{-# language CPP #-}
-- | = Name
--
-- VK_ANDROID_external_format_resolve - device extension
--
-- == VK_ANDROID_external_format_resolve
--
-- [__Name String__]
--     @VK_ANDROID_external_format_resolve@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     469
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ANDROID_external_memory_android_hardware_buffer VK_ANDROID_external_memory_android_hardware_buffer>
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse OpenGL \/ ES support>
--
-- [__Contact__]
--
--     -   Chris Forbes
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_ANDROID_external_format_resolve] @chrisforbes%0A*Here describe the issue or question you have about the VK_ANDROID_external_format_resolve extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_ANDROID_external_format_resolve.adoc VK_ANDROID_external_format_resolve>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-05-03
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Tobias Hector, AMD
--
--     -   Chris Forbes, Google
--
--     -   Jan-Harald Fredriksen, Arm
--
--     -   Shahbaz Youssefi, Google
--
--     -   Matthew Netsch, Qualcomm
--
--     -   Tony Zlatsinki, Nvidia
--
--     -   Daniel Koch, Nvidia
--
--     -   Jeff Leger, Qualcomm
--
--     -   Alex Walters, Imagination
--
--     -   Andrew Garrard, Imagination
--
--     -   Ralph Potter, Samsung
--
--     -   Ian Elliott, Google
--
-- == Description
--
-- This extension enables rendering to Android Hardware Buffers with
-- external formats which cannot be directly represented as renderable in
-- Vulkan, including Y′CBCR formats.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferPropertiesANDROID':
--
--     -   'AndroidHardwareBufferFormatResolvePropertiesANDROID'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceExternalFormatResolveFeaturesANDROID'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceExternalFormatResolvePropertiesANDROID'
--
-- == New Enum Constants
--
-- -   'ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME'
--
-- -   'ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_RESOLVE_PROPERTIES_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_FEATURES_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_PROPERTIES_ANDROID'
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_dynamic_rendering VK_KHR_dynamic_rendering>
-- is supported:
--
-- -   Extending
--     'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits':
--
--     -   'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_EXTERNAL_FORMAT_DOWNSAMPLE_ANDROID'
--
-- == Version History
--
-- -   Revision 1, 2023-05-34 (Tobias Hector)
--
--     -   Initial version
--
-- == See Also
--
-- 'AndroidHardwareBufferFormatResolvePropertiesANDROID',
-- 'PhysicalDeviceExternalFormatResolveFeaturesANDROID',
-- 'PhysicalDeviceExternalFormatResolvePropertiesANDROID'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_ANDROID_external_format_resolve Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_ANDROID_external_format_resolve  ( PhysicalDeviceExternalFormatResolveFeaturesANDROID(..)
                                                             , PhysicalDeviceExternalFormatResolvePropertiesANDROID(..)
                                                             , AndroidHardwareBufferFormatResolvePropertiesANDROID(..)
                                                             , ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION
                                                             , pattern ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION
                                                             , ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME
                                                             , pattern ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME
                                                             ) where

import Foreign.Marshal.Alloc (allocaBytes)
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 Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core11.Enums.ChromaLocation (ChromaLocation)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_RESOLVE_PROPERTIES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_FEATURES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_PROPERTIES_ANDROID))
-- | VkPhysicalDeviceExternalFormatResolveFeaturesANDROID - Structure
-- describing whether external format resolves are supported
--
-- = Description
--
-- If the 'PhysicalDeviceExternalFormatResolveFeaturesANDROID' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceExternalFormatResolveFeaturesANDROID' /can/
-- also be used in the @pNext@ chain of
-- 'Vulkan.Core10.Device.DeviceCreateInfo' to selectively enable these
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ANDROID_external_format_resolve VK_ANDROID_external_format_resolve>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExternalFormatResolveFeaturesANDROID = PhysicalDeviceExternalFormatResolveFeaturesANDROID
  { -- | #features-externalFormatResolve# @externalFormatResolve@ specifies
    -- whether external format resolves are supported.
    PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
externalFormatResolve :: Bool }
  deriving (Typeable, PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
$c/= :: PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
== :: PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
$c== :: PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExternalFormatResolveFeaturesANDROID)
#endif
deriving instance Show PhysicalDeviceExternalFormatResolveFeaturesANDROID

instance ToCStruct PhysicalDeviceExternalFormatResolveFeaturesANDROID where
  withCStruct :: forall b.
PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> (Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID -> IO b)
-> IO b
withCStruct PhysicalDeviceExternalFormatResolveFeaturesANDROID
x Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p PhysicalDeviceExternalFormatResolveFeaturesANDROID
x (Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID -> IO b
f Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p PhysicalDeviceExternalFormatResolveFeaturesANDROID{Bool
externalFormatResolve :: Bool
$sel:externalFormatResolve:PhysicalDeviceExternalFormatResolveFeaturesANDROID :: PhysicalDeviceExternalFormatResolveFeaturesANDROID -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_FEATURES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
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 PhysicalDeviceExternalFormatResolveFeaturesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
externalFormatResolve))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_FEATURES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
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 PhysicalDeviceExternalFormatResolveFeaturesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceExternalFormatResolveFeaturesANDROID where
  peekCStruct :: Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
-> IO PhysicalDeviceExternalFormatResolveFeaturesANDROID
peekCStruct Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
p = do
    Bool32
externalFormatResolve <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExternalFormatResolveFeaturesANDROID
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
$ Bool -> PhysicalDeviceExternalFormatResolveFeaturesANDROID
PhysicalDeviceExternalFormatResolveFeaturesANDROID
             (Bool32 -> Bool
bool32ToBool Bool32
externalFormatResolve)

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

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


-- | VkPhysicalDeviceExternalFormatResolvePropertiesANDROID - Structure
-- describing external format resolve supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceExternalFormatResolvePropertiesANDROID' structure
-- is included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ANDROID_external_format_resolve VK_ANDROID_external_format_resolve>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core11.Enums.ChromaLocation.ChromaLocation',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExternalFormatResolvePropertiesANDROID = PhysicalDeviceExternalFormatResolvePropertiesANDROID
  { -- | #limits-nullColorAttachmentWithExternalFormatResolve#
    -- @nullColorAttachmentWithExternalFormatResolve@ indicates that there
    -- /must/ be no color attachment image when performing external format
    -- resolves if it is 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
nullColorAttachmentWithExternalFormatResolve :: Bool
  , -- | #limits-externalFormatResolveChromaOffsetX#
    -- @externalFormatResolveChromaOffsetX@ indicates the
    -- 'Vulkan.Core11.Enums.ChromaLocation.ChromaLocation' that an
    -- implementation uses in the X axis for accesses to an external format
    -- image as a resolve attachment. This /must/ be consistent between
    -- external format resolves and load operations from external format
    -- resolve attachments to color attachments when
    -- @nullColorAttachmentWithExternalFormatResolve@ is
    -- 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> ChromaLocation
externalFormatResolveChromaOffsetX :: ChromaLocation
  , -- | #limits-externalFormatResolveChromaOffsetY#
    -- @externalFormatResolveChromaOffsetY@ indicates the
    -- 'Vulkan.Core11.Enums.ChromaLocation.ChromaLocation' that an
    -- implementation uses in the Y axis for accesses to an external format
    -- image as a resolve attachment. This /must/ be consistent between
    -- external format resolves and load operations from external format
    -- resolve attachments to color attachments when
    -- @nullColorAttachmentWithExternalFormatResolve@ is
    -- 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> ChromaLocation
externalFormatResolveChromaOffsetY :: ChromaLocation
  }
  deriving (Typeable, PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
$c/= :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
== :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
$c== :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExternalFormatResolvePropertiesANDROID)
#endif
deriving instance Show PhysicalDeviceExternalFormatResolvePropertiesANDROID

instance ToCStruct PhysicalDeviceExternalFormatResolvePropertiesANDROID where
  withCStruct :: forall b.
PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> (Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
    -> IO b)
-> IO b
withCStruct PhysicalDeviceExternalFormatResolvePropertiesANDROID
x Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p PhysicalDeviceExternalFormatResolvePropertiesANDROID
x (Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID -> IO b
f Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p PhysicalDeviceExternalFormatResolvePropertiesANDROID{Bool
ChromaLocation
externalFormatResolveChromaOffsetY :: ChromaLocation
externalFormatResolveChromaOffsetX :: ChromaLocation
nullColorAttachmentWithExternalFormatResolve :: Bool
$sel:externalFormatResolveChromaOffsetY:PhysicalDeviceExternalFormatResolvePropertiesANDROID :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> ChromaLocation
$sel:externalFormatResolveChromaOffsetX:PhysicalDeviceExternalFormatResolvePropertiesANDROID :: PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> ChromaLocation
$sel:nullColorAttachmentWithExternalFormatResolve:PhysicalDeviceExternalFormatResolvePropertiesANDROID :: PhysicalDeviceExternalFormatResolvePropertiesANDROID -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_PROPERTIES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
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 PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nullColorAttachmentWithExternalFormatResolve))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ChromaLocation)) (ChromaLocation
externalFormatResolveChromaOffsetX)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ChromaLocation)) (ChromaLocation
externalFormatResolveChromaOffsetY)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FORMAT_RESOLVE_PROPERTIES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
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 PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ChromaLocation)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceExternalFormatResolvePropertiesANDROID where
  peekCStruct :: Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
-> IO PhysicalDeviceExternalFormatResolvePropertiesANDROID
peekCStruct Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p = do
    Bool32
nullColorAttachmentWithExternalFormatResolve <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    ChromaLocation
externalFormatResolveChromaOffsetX <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr ChromaLocation))
    ChromaLocation
externalFormatResolveChromaOffsetY <- forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr PhysicalDeviceExternalFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ChromaLocation))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> ChromaLocation
-> ChromaLocation
-> PhysicalDeviceExternalFormatResolvePropertiesANDROID
PhysicalDeviceExternalFormatResolvePropertiesANDROID
             (Bool32 -> Bool
bool32ToBool Bool32
nullColorAttachmentWithExternalFormatResolve)
             ChromaLocation
externalFormatResolveChromaOffsetX
             ChromaLocation
externalFormatResolveChromaOffsetY

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

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


-- | VkAndroidHardwareBufferFormatResolvePropertiesANDROID - Structure
-- defining properties of resolves using an external format
--
-- = Description
--
-- Any Android hardware buffer created with the @GRALLOC_USAGE_HW_RENDER@
-- flag /must/ be renderable in some way in Vulkan, either:
--
-- -   'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferFormatPropertiesANDROID'::@format@
--     /must/ be a format that supports
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--     or
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--     in
--     'Vulkan.Core10.DeviceInitialization.FormatProperties'::@optimalTilingFeatures@;
--     or
--
-- -   @colorAttachmentFormat@ /must/ be a format that supports
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--     in
--     'Vulkan.Core10.DeviceInitialization.FormatProperties'::@optimalTilingFeatures@.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkAndroidHardwareBufferFormatResolvePropertiesANDROID-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_RESOLVE_PROPERTIES_ANDROID'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_ANDROID_external_format_resolve VK_ANDROID_external_format_resolve>,
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AndroidHardwareBufferFormatResolvePropertiesANDROID = AndroidHardwareBufferFormatResolvePropertiesANDROID
  { -- | @colorAttachmentFormat@ is a 'Vulkan.Core10.Enums.Format.Format'
    -- specifying the format of color attachment images that /must/ be used for
    -- color attachments when resolving to the specified external format. If
    -- the implementation supports external format resolves for the specified
    -- external format, this value will be set to a color format supporting the
    -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
    -- in
    -- 'Vulkan.Core10.DeviceInitialization.FormatProperties'::@optimalTilingFeatures@
    -- as returned by
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties'
    -- with @format@ equal to @colorAttachmentFormat@ If external format
    -- resolves are not supported, this value will be set to
    -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED'.
    AndroidHardwareBufferFormatResolvePropertiesANDROID -> Format
colorAttachmentFormat :: Format }
  deriving (Typeable, AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID -> Bool
$c/= :: AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID -> Bool
== :: AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID -> Bool
$c== :: AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferFormatResolvePropertiesANDROID)
#endif
deriving instance Show AndroidHardwareBufferFormatResolvePropertiesANDROID

instance ToCStruct AndroidHardwareBufferFormatResolvePropertiesANDROID where
  withCStruct :: forall b.
AndroidHardwareBufferFormatResolvePropertiesANDROID
-> (Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
    -> IO b)
-> IO b
withCStruct AndroidHardwareBufferFormatResolvePropertiesANDROID
x Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p AndroidHardwareBufferFormatResolvePropertiesANDROID
x (Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID -> IO b
f Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p)
  pokeCStruct :: forall b.
Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
-> AndroidHardwareBufferFormatResolvePropertiesANDROID
-> IO b
-> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p AndroidHardwareBufferFormatResolvePropertiesANDROID{Format
colorAttachmentFormat :: Format
$sel:colorAttachmentFormat:AndroidHardwareBufferFormatResolvePropertiesANDROID :: AndroidHardwareBufferFormatResolvePropertiesANDROID -> Format
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_RESOLVE_PROPERTIES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
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 AndroidHardwareBufferFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
colorAttachmentFormat)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
-> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_RESOLVE_PROPERTIES_ANDROID)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
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 AndroidHardwareBufferFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AndroidHardwareBufferFormatResolvePropertiesANDROID where
  peekCStruct :: Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
-> IO AndroidHardwareBufferFormatResolvePropertiesANDROID
peekCStruct Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p = do
    Format
colorAttachmentFormat <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AndroidHardwareBufferFormatResolvePropertiesANDROID
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Format -> AndroidHardwareBufferFormatResolvePropertiesANDROID
AndroidHardwareBufferFormatResolvePropertiesANDROID
             Format
colorAttachmentFormat

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

instance Zero AndroidHardwareBufferFormatResolvePropertiesANDROID where
  zero :: AndroidHardwareBufferFormatResolvePropertiesANDROID
zero = Format -> AndroidHardwareBufferFormatResolvePropertiesANDROID
AndroidHardwareBufferFormatResolvePropertiesANDROID
           forall a. Zero a => a
zero


type ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION"
pattern ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION :: forall a . Integral a => a
pattern $bANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION :: forall a. Integral a => a
$mANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ANDROID_EXTERNAL_FORMAT_RESOLVE_SPEC_VERSION = 1


type ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME = "VK_ANDROID_external_format_resolve"

-- No documentation found for TopLevel "VK_ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME"
pattern ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
ANDROID_EXTERNAL_FORMAT_RESOLVE_EXTENSION_NAME = "VK_ANDROID_external_format_resolve"