{-# language CPP #-}
-- | = Name
--
-- VK_ANDROID_external_memory_android_hardware_buffer - device extension
--
-- == VK_ANDROID_external_memory_android_hardware_buffer
--
-- [__Name String__]
--     @VK_ANDROID_external_memory_android_hardware_buffer@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     130
--
-- [__Revision__]
--     5
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_sampler_ycbcr_conversion@
--
--     -   Requires @VK_KHR_external_memory@
--
--     -   Requires @VK_EXT_queue_family_foreign@
--
--     -   Requires @VK_KHR_dedicated_allocation@
--
-- [__Contact__]
--
--     -   Jesse Hall
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_ANDROID_external_memory_android_hardware_buffer] @critsec%0A<<Here describe the issue or question you have about the VK_ANDROID_external_memory_android_hardware_buffer extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2021-09-30
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Ray Smith, ARM
--
--     -   Chad Versace, Google
--
--     -   Jesse Hall, Google
--
--     -   Tobias Hector, Imagination
--
--     -   James Jones, NVIDIA
--
--     -   Tony Zlatinski, NVIDIA
--
--     -   Matthew Netsch, Qualcomm
--
--     -   Andrew Garrard, Samsung
--
-- == Description
--
-- This extension enables an application to import Android
-- 'AHardwareBuffer' objects created outside of the Vulkan device into
-- Vulkan memory objects, where they /can/ be bound to images and buffers.
-- It also allows exporting an 'AHardwareBuffer' from a Vulkan memory
-- object for symmetry with other operating systems. But since not all
-- 'AHardwareBuffer' usages and formats have Vulkan equivalents, exporting
-- from Vulkan provides strictly less functionality than creating the
-- 'AHardwareBuffer' externally and importing it.
--
-- Some 'AHardwareBuffer' images have implementation-defined /external
-- formats/ that /may/ not correspond to Vulkan formats. Sampler Y′CBCR
-- conversion /can/ be used to sample from these images and convert them to
-- a known color space.
--
-- == New Base Types
--
-- -   'AHardwareBuffer'
--
-- == New Commands
--
-- -   'getAndroidHardwareBufferPropertiesANDROID'
--
-- -   'getMemoryAndroidHardwareBufferANDROID'
--
-- == New Structures
--
-- -   'AndroidHardwareBufferPropertiesANDROID'
--
-- -   'MemoryGetAndroidHardwareBufferInfoANDROID'
--
-- -   Extending 'AndroidHardwareBufferPropertiesANDROID':
--
--     -   'AndroidHardwareBufferFormatPropertiesANDROID'
--
-- -   Extending 'Vulkan.Core10.Image.ImageCreateInfo',
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo':
--
--     -   'ExternalFormatANDROID'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.ImageFormatProperties2':
--
--     -   'AndroidHardwareBufferUsageANDROID'
--
-- -   Extending 'Vulkan.Core10.Memory.MemoryAllocateInfo':
--
--     -   'ImportAndroidHardwareBufferInfoANDROID'
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_format_feature_flags2 VK_KHR_format_feature_flags2>
-- is supported:
--
-- -   Extending 'AndroidHardwareBufferPropertiesANDROID':
--
--     -   'AndroidHardwareBufferFormatProperties2ANDROID'
--
-- == New Enum Constants
--
-- -   'ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME'
--
-- -   'ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION'
--
-- -   Extending
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits':
--
--     -   'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID'
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_format_feature_flags2 VK_KHR_format_feature_flags2>
-- is supported:
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID'
--
-- == Issues
--
-- 1) Other external memory objects are represented as weakly-typed handles
-- (e.g. Win32 'Vulkan.Extensions.VK_NV_external_memory_win32.HANDLE' or
-- POSIX file descriptor), and require a handle type parameter along with
-- handles. 'AHardwareBuffer' is strongly typed, so naming the handle type
-- is redundant. Does symmetry justify adding handle type
-- parameters\/fields anyway?
--
-- __RESOLVED__: No. The handle type is already provided in places that
-- treat external memory objects generically. In the places we would add
-- it, the application code that would have to provide the handle type
-- value is already dealing with 'AHardwareBuffer'-specific
-- commands\/structures; the extra symmetry would not be enough to make
-- that code generic.
--
-- 2) The internal layout and therefore size of a 'AHardwareBuffer' image
-- may depend on native usage flags that do not have corresponding Vulkan
-- counterparts. Do we provide this information to
-- 'Vulkan.Core10.Image.createImage' somehow, or allow the allocation size
-- reported by 'Vulkan.Core10.MemoryManagement.getImageMemoryRequirements'
-- to be approximate?
--
-- __RESOLVED__: Allow the allocation size to be unspecified when
-- allocating the memory. It has to work this way for exported image memory
-- anyway, since 'AHardwareBuffer' allocation happens in
-- 'Vulkan.Core10.Memory.allocateMemory', and internally is performed by a
-- separate HAL, not the Vulkan implementation itself. There is a similar
-- issue with 'Vulkan.Core10.Image.getImageSubresourceLayout': the layout
-- is determined by the allocator HAL, so it is not known until the image
-- is bound to memory.
--
-- 3) Should the result of sampling an external-format image with the
-- suggested Y′CBCR conversion parameters yield the same results as using a
-- @samplerExternalOES@ in OpenGL ES?
--
-- __RESOLVED__: This would be desirable, so that apps converting from
-- OpenGL ES to Vulkan could get the same output given the same input. But
-- since sampling and conversion from Y′CBCR images is so loosely defined
-- in OpenGL ES, multiple implementations do it in a way that does not
-- conform to Vulkan’s requirements. Modifying the OpenGL ES implementation
-- would be difficult, and would change the output of existing unmodified
-- applications. Changing the output only for applications that are being
-- modified gives developers the chance to notice and mitigate any
-- problems. Implementations are encouraged to minimize differences as much
-- as possible without causing compatibility problems for existing OpenGL
-- ES applications or violating Vulkan requirements.
--
-- 4) Should an 'AHardwareBuffer' with @AHARDWAREBUFFER_USAGE_CPU_*@ usage
-- be mappable in Vulkan? Should it be possible to export an
-- @AHardwareBuffers@ with such usage?
--
-- __RESOLVED__: Optional, and mapping in Vulkan is not the same as
-- @AHardwareBuffer_lock@. The semantics of these are different: mapping in
-- memory is persistent, just gives a raw view of the memory contents, and
-- does not involve ownership. @AHardwareBuffer_lock@ gives the host
-- exclusive access to the buffer, is temporary, and allows for
-- reformatting copy-in\/copy-out. Implementations are not required to
-- support host-visible memory types for imported Android hardware buffers
-- or resources backed by them. If a host-visible memory type is supported
-- and used, the memory can be mapped in Vulkan, but doing so follows
-- Vulkan semantics: it is just a raw view of the data and does not imply
-- ownership (this means implementations must not internally call
-- @AHardwareBuffer_lock@ to implement 'Vulkan.Core10.Memory.mapMemory', or
-- assume the application has done so). Implementations are not required to
-- support linear-tiled images backed by Android hardware buffers, even if
-- the 'AHardwareBuffer' has CPU usage. There is no reliable way to
-- allocate memory in Vulkan that can be exported to a 'AHardwareBuffer'
-- with CPU usage.
--
-- 5) Android may add new 'AHardwareBuffer' formats and usage flags over
-- time. Can reference to them be added to this extension, or do they need
-- a new extension?
--
-- __RESOLVED__: This extension can document the interaction between the
-- new AHB formats\/usages and existing Vulkan features. No new Vulkan
-- features or implementation requirements can be added. The extension
-- version number will be incremented when this additional documentation is
-- added, but the version number does not indicate that an implementation
-- supports Vulkan memory or resources that map to the new
-- 'AHardwareBuffer' features: support for that must be queried with
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
-- or is implied by successfully allocating a 'AHardwareBuffer' outside of
-- Vulkan that uses the new feature and has a GPU usage flag.
--
-- In essence, these are new features added to a new Android API level,
-- rather than new Vulkan features. The extension will only document how
-- existing Vulkan features map to that new Android feature.
--
-- == Version History
--
-- -   Revision 5, 2022-02-04 (Chris Forbes)
--
--     -   Describe mapping of flags for storage image support
--
-- -   Revision 4, 2021-09-30 (Jon Leech)
--
--     -   Add interaction with @VK_KHR_format_feature_flags2@ to @vk.xml@
--
-- -   Revision 3, 2019-08-27 (Jon Leech)
--
--     -   Update revision history to correspond to XML version number
--
-- -   Revision 2, 2018-04-09 (Petr Kraus)
--
--     -   Markup fixes and remove incorrect Draft status
--
-- -   Revision 1, 2018-03-04 (Jesse Hall)
--
--     -   Initial version
--
-- == See Also
--
-- 'AHardwareBuffer', 'AndroidHardwareBufferFormatPropertiesANDROID',
-- 'AndroidHardwareBufferPropertiesANDROID',
-- 'AndroidHardwareBufferUsageANDROID', 'ExternalFormatANDROID',
-- 'ImportAndroidHardwareBufferInfoANDROID',
-- 'MemoryGetAndroidHardwareBufferInfoANDROID',
-- 'getAndroidHardwareBufferPropertiesANDROID',
-- 'getMemoryAndroidHardwareBufferANDROID'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#VK_ANDROID_external_memory_android_hardware_buffer 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_memory_android_hardware_buffer  ( getAndroidHardwareBufferPropertiesANDROID
                                                                             , getMemoryAndroidHardwareBufferANDROID
                                                                             , ImportAndroidHardwareBufferInfoANDROID(..)
                                                                             , AndroidHardwareBufferUsageANDROID(..)
                                                                             , AndroidHardwareBufferPropertiesANDROID(..)
                                                                             , MemoryGetAndroidHardwareBufferInfoANDROID(..)
                                                                             , AndroidHardwareBufferFormatPropertiesANDROID(..)
                                                                             , ExternalFormatANDROID(..)
                                                                             , AndroidHardwareBufferFormatProperties2ANDROID(..)
                                                                             , ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION
                                                                             , pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION
                                                                             , ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME
                                                                             , pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME
                                                                             , AHardwareBuffer
                                                                             ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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.Type.Equality ((:~:)(Refl))
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.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core11.Enums.ChromaLocation (ChromaLocation)
import Vulkan.Core10.ImageView (ComponentMapping)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetAndroidHardwareBufferPropertiesANDROID))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryAndroidHardwareBufferANDROID))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.Core13.Enums.FormatFeatureFlags2 (FormatFeatureFlags2)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core11.Enums.SamplerYcbcrModelConversion (SamplerYcbcrModelConversion)
import Vulkan.Core11.Enums.SamplerYcbcrRange (SamplerYcbcrRange)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetAndroidHardwareBufferPropertiesANDROID
  :: FunPtr (Ptr Device_T -> Ptr AHardwareBuffer -> Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID) -> IO Result) -> Ptr Device_T -> Ptr AHardwareBuffer -> Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID) -> IO Result

-- | vkGetAndroidHardwareBufferPropertiesANDROID - Get Properties of External
-- Memory Android Hardware Buffers
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Extensions.VK_KHR_external_memory.ERROR_INVALID_EXTERNAL_HANDLE_KHR'
--
-- = See Also
--
-- <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>,
-- 'AndroidHardwareBufferPropertiesANDROID', 'Vulkan.Core10.Handles.Device'
getAndroidHardwareBufferPropertiesANDROID :: forall a io
                                           . (Extendss AndroidHardwareBufferPropertiesANDROID a, PokeChain a, PeekChain a, MonadIO io)
                                          => -- | @device@ is the logical device that will be importing @buffer@.
                                             --
                                             -- #VUID-vkGetAndroidHardwareBufferPropertiesANDROID-device-parameter#
                                             -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                             Device
                                          -> -- | @buffer@ is the Android hardware buffer which will be imported.
                                             --
                                             -- #VUID-vkGetAndroidHardwareBufferPropertiesANDROID-buffer-01884# @buffer@
                                             -- /must/ be a valid Android hardware buffer object with at least one of
                                             -- the @AHARDWAREBUFFER_USAGE_GPU_*@ flags in its
                                             -- @AHardwareBuffer_Desc@::@usage@
                                             --
                                             -- #VUID-vkGetAndroidHardwareBufferPropertiesANDROID-buffer-parameter#
                                             -- @buffer@ /must/ be a valid pointer to a valid 'AHardwareBuffer' value
                                             (Ptr AHardwareBuffer)
                                          -> io (AndroidHardwareBufferPropertiesANDROID a)
getAndroidHardwareBufferPropertiesANDROID :: Device
-> Ptr AHardwareBuffer
-> io (AndroidHardwareBufferPropertiesANDROID a)
getAndroidHardwareBufferPropertiesANDROID Device
device Ptr AHardwareBuffer
buffer = IO (AndroidHardwareBufferPropertiesANDROID a)
-> io (AndroidHardwareBufferPropertiesANDROID a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (AndroidHardwareBufferPropertiesANDROID a)
 -> io (AndroidHardwareBufferPropertiesANDROID a))
-> (ContT
      (AndroidHardwareBufferPropertiesANDROID a)
      IO
      (AndroidHardwareBufferPropertiesANDROID a)
    -> IO (AndroidHardwareBufferPropertiesANDROID a))
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
-> io (AndroidHardwareBufferPropertiesANDROID a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (AndroidHardwareBufferPropertiesANDROID a)
  IO
  (AndroidHardwareBufferPropertiesANDROID a)
-> IO (AndroidHardwareBufferPropertiesANDROID a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (AndroidHardwareBufferPropertiesANDROID a)
   IO
   (AndroidHardwareBufferPropertiesANDROID a)
 -> io (AndroidHardwareBufferPropertiesANDROID a))
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
-> io (AndroidHardwareBufferPropertiesANDROID a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetAndroidHardwareBufferPropertiesANDROIDPtr :: FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Ptr AHardwareBuffer
      -> ("pProperties"
          ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
      -> IO Result)
pVkGetAndroidHardwareBufferPropertiesANDROID (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ())
-> IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Ptr AHardwareBuffer
      -> ("pProperties"
          ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetAndroidHardwareBufferPropertiesANDROID is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetAndroidHardwareBufferPropertiesANDROID' :: Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
    ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
vkGetAndroidHardwareBufferPropertiesANDROID' = FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
-> Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
    ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
mkVkGetAndroidHardwareBufferPropertiesANDROID FunPtr
  (Ptr Device_T
   -> Ptr AHardwareBuffer
   -> ("pProperties"
       ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
   -> IO Result)
vkGetAndroidHardwareBufferPropertiesANDROIDPtr
  Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties <- ((Ptr (AndroidHardwareBufferPropertiesANDROID a)
  -> IO (AndroidHardwareBufferPropertiesANDROID a))
 -> IO (AndroidHardwareBufferPropertiesANDROID a))
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (Ptr (AndroidHardwareBufferPropertiesANDROID a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (AndroidHardwareBufferPropertiesANDROID a) =>
(Ptr (AndroidHardwareBufferPropertiesANDROID a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(AndroidHardwareBufferPropertiesANDROID _))
  Result
r <- IO Result
-> ContT (AndroidHardwareBufferPropertiesANDROID a) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO Result)
-> IO Result
-> ContT (AndroidHardwareBufferPropertiesANDROID a) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetAndroidHardwareBufferPropertiesANDROID" (Ptr Device_T
-> Ptr AHardwareBuffer
-> ("pProperties"
    ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID))
-> IO Result
vkGetAndroidHardwareBufferPropertiesANDROID' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr AHardwareBuffer
buffer) (Ptr (AndroidHardwareBufferPropertiesANDROID a)
-> "pProperties"
   ::: Ptr (SomeStruct AndroidHardwareBufferPropertiesANDROID)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties)))
  IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ())
-> IO () -> ContT (AndroidHardwareBufferPropertiesANDROID a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  AndroidHardwareBufferPropertiesANDROID a
pProperties <- IO (AndroidHardwareBufferPropertiesANDROID a)
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (AndroidHardwareBufferPropertiesANDROID a)
 -> ContT
      (AndroidHardwareBufferPropertiesANDROID a)
      IO
      (AndroidHardwareBufferPropertiesANDROID a))
-> IO (AndroidHardwareBufferPropertiesANDROID a)
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
forall a b. (a -> b) -> a -> b
$ Ptr (AndroidHardwareBufferPropertiesANDROID a)
-> IO (AndroidHardwareBufferPropertiesANDROID a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(AndroidHardwareBufferPropertiesANDROID _) Ptr (AndroidHardwareBufferPropertiesANDROID a)
pPProperties
  AndroidHardwareBufferPropertiesANDROID a
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AndroidHardwareBufferPropertiesANDROID a
 -> ContT
      (AndroidHardwareBufferPropertiesANDROID a)
      IO
      (AndroidHardwareBufferPropertiesANDROID a))
-> AndroidHardwareBufferPropertiesANDROID a
-> ContT
     (AndroidHardwareBufferPropertiesANDROID a)
     IO
     (AndroidHardwareBufferPropertiesANDROID a)
forall a b. (a -> b) -> a -> b
$ (AndroidHardwareBufferPropertiesANDROID a
pProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMemoryAndroidHardwareBufferANDROID
  :: FunPtr (Ptr Device_T -> Ptr MemoryGetAndroidHardwareBufferInfoANDROID -> Ptr (Ptr AHardwareBuffer) -> IO Result) -> Ptr Device_T -> Ptr MemoryGetAndroidHardwareBufferInfoANDROID -> Ptr (Ptr AHardwareBuffer) -> IO Result

-- | vkGetMemoryAndroidHardwareBufferANDROID - Get an Android hardware buffer
-- for a memory object
--
-- = Description
--
-- Each call to 'getMemoryAndroidHardwareBufferANDROID' /must/ return an
-- Android hardware buffer with a new reference acquired in addition to the
-- reference held by the 'Vulkan.Core10.Handles.DeviceMemory'. To avoid
-- leaking resources, the application /must/ release the reference by
-- calling @AHardwareBuffer_release@ when it is no longer needed. When
-- called with the same handle in
-- 'MemoryGetAndroidHardwareBufferInfoANDROID'::@memory@,
-- 'getMemoryAndroidHardwareBufferANDROID' /must/ return the same Android
-- hardware buffer object. If the device memory was created by importing an
-- Android hardware buffer, 'getMemoryAndroidHardwareBufferANDROID' /must/
-- return that same Android hardware buffer object.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.Handles.Device',
-- 'MemoryGetAndroidHardwareBufferInfoANDROID'
getMemoryAndroidHardwareBufferANDROID :: forall io
                                       . (MonadIO io)
                                      => -- | @device@ is the logical device that created the device memory being
                                         -- exported.
                                         --
                                         -- #VUID-vkGetMemoryAndroidHardwareBufferANDROID-device-parameter# @device@
                                         -- /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                         Device
                                      -> -- | @pInfo@ is a pointer to a 'MemoryGetAndroidHardwareBufferInfoANDROID'
                                         -- structure containing parameters of the export operation.
                                         --
                                         -- #VUID-vkGetMemoryAndroidHardwareBufferANDROID-pInfo-parameter# @pInfo@
                                         -- /must/ be a valid pointer to a valid
                                         -- 'MemoryGetAndroidHardwareBufferInfoANDROID' structure
                                         MemoryGetAndroidHardwareBufferInfoANDROID
                                      -> io (Ptr AHardwareBuffer)
getMemoryAndroidHardwareBufferANDROID :: Device
-> MemoryGetAndroidHardwareBufferInfoANDROID
-> io (Ptr AHardwareBuffer)
getMemoryAndroidHardwareBufferANDROID Device
device MemoryGetAndroidHardwareBufferInfoANDROID
info = IO (Ptr AHardwareBuffer) -> io (Ptr AHardwareBuffer)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr AHardwareBuffer) -> io (Ptr AHardwareBuffer))
-> (ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
    -> IO (Ptr AHardwareBuffer))
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
-> io (Ptr AHardwareBuffer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
-> IO (Ptr AHardwareBuffer)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
 -> io (Ptr AHardwareBuffer))
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
-> io (Ptr AHardwareBuffer)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetMemoryAndroidHardwareBufferANDROIDPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
      -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
      -> IO Result)
pVkGetMemoryAndroidHardwareBufferANDROID (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT (Ptr AHardwareBuffer) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Ptr AHardwareBuffer) IO ())
-> IO () -> ContT (Ptr AHardwareBuffer) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
      -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetMemoryAndroidHardwareBufferANDROID is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetMemoryAndroidHardwareBufferANDROID' :: Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
vkGetMemoryAndroidHardwareBufferANDROID' = FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
mkVkGetMemoryAndroidHardwareBufferANDROID FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO Result)
vkGetMemoryAndroidHardwareBufferANDROIDPtr
  "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
pInfo <- ((("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
  -> IO (Ptr AHardwareBuffer))
 -> IO (Ptr AHardwareBuffer))
-> ContT
     (Ptr AHardwareBuffer)
     IO
     ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
   -> IO (Ptr AHardwareBuffer))
  -> IO (Ptr AHardwareBuffer))
 -> ContT
      (Ptr AHardwareBuffer)
      IO
      ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID))
-> ((("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
     -> IO (Ptr AHardwareBuffer))
    -> IO (Ptr AHardwareBuffer))
-> ContT
     (Ptr AHardwareBuffer)
     IO
     ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
forall a b. (a -> b) -> a -> b
$ MemoryGetAndroidHardwareBufferInfoANDROID
-> (("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
    -> IO (Ptr AHardwareBuffer))
-> IO (Ptr AHardwareBuffer)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryGetAndroidHardwareBufferInfoANDROID
info)
  "pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer <- ((("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
  -> IO (Ptr AHardwareBuffer))
 -> IO (Ptr AHardwareBuffer))
-> ContT
     (Ptr AHardwareBuffer) IO ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
   -> IO (Ptr AHardwareBuffer))
  -> IO (Ptr AHardwareBuffer))
 -> ContT
      (Ptr AHardwareBuffer) IO ("pBuffer" ::: Ptr (Ptr AHardwareBuffer)))
-> ((("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
     -> IO (Ptr AHardwareBuffer))
    -> IO (Ptr AHardwareBuffer))
-> ContT
     (Ptr AHardwareBuffer) IO ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
forall a b. (a -> b) -> a -> b
$ IO ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> (("pBuffer" ::: Ptr (Ptr AHardwareBuffer)) -> IO ())
-> (("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
    -> IO (Ptr AHardwareBuffer))
-> IO (Ptr AHardwareBuffer)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr AHardwareBuffer) Int
8) ("pBuffer" ::: Ptr (Ptr AHardwareBuffer)) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT (Ptr AHardwareBuffer) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Ptr AHardwareBuffer) IO Result)
-> IO Result -> ContT (Ptr AHardwareBuffer) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetMemoryAndroidHardwareBufferANDROID" (Ptr Device_T
-> ("pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID)
-> ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO Result
vkGetMemoryAndroidHardwareBufferANDROID' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pInfo" ::: Ptr MemoryGetAndroidHardwareBufferInfoANDROID
pInfo ("pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer))
  IO () -> ContT (Ptr AHardwareBuffer) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Ptr AHardwareBuffer) IO ())
-> IO () -> ContT (Ptr AHardwareBuffer) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Ptr AHardwareBuffer
pBuffer <- IO (Ptr AHardwareBuffer)
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr AHardwareBuffer)
 -> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer))
-> IO (Ptr AHardwareBuffer)
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
forall a b. (a -> b) -> a -> b
$ ("pBuffer" ::: Ptr (Ptr AHardwareBuffer))
-> IO (Ptr AHardwareBuffer)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AHardwareBuffer) "pBuffer" ::: Ptr (Ptr AHardwareBuffer)
pPBuffer
  Ptr AHardwareBuffer
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr AHardwareBuffer
 -> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer))
-> Ptr AHardwareBuffer
-> ContT (Ptr AHardwareBuffer) IO (Ptr AHardwareBuffer)
forall a b. (a -> b) -> a -> b
$ (Ptr AHardwareBuffer
pBuffer)


-- | VkImportAndroidHardwareBufferInfoANDROID - Import memory from an Android
-- hardware buffer
--
-- = Description
--
-- If the 'Vulkan.Core10.Memory.allocateMemory' command succeeds, the
-- implementation /must/ acquire a reference to the imported hardware
-- buffer, which it /must/ release when the device memory object is freed.
-- If the command fails, the implementation /must/ not retain a reference.
--
-- == Valid Usage
--
-- -   #VUID-VkImportAndroidHardwareBufferInfoANDROID-buffer-01880# If
--     @buffer@ is not @NULL@, Android hardware buffers /must/ be supported
--     for import, as reported by
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalImageFormatProperties'
--     or
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalBufferProperties'
--
-- -   #VUID-VkImportAndroidHardwareBufferInfoANDROID-buffer-01881# If
--     @buffer@ is not @NULL@, it /must/ be a valid Android hardware buffer
--     object with @AHardwareBuffer_Desc@::@usage@ compatible with Vulkan
--     as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer Android Hardware Buffers>
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkImportAndroidHardwareBufferInfoANDROID-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID'
--
-- -   #VUID-VkImportAndroidHardwareBufferInfoANDROID-buffer-parameter#
--     @buffer@ /must/ be a valid pointer to an 'AHardwareBuffer' value
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ImportAndroidHardwareBufferInfoANDROID = ImportAndroidHardwareBufferInfoANDROID
  { -- | @buffer@ is the Android hardware buffer to import.
    ImportAndroidHardwareBufferInfoANDROID -> Ptr AHardwareBuffer
buffer :: Ptr AHardwareBuffer }
  deriving (Typeable, ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
(ImportAndroidHardwareBufferInfoANDROID
 -> ImportAndroidHardwareBufferInfoANDROID -> Bool)
-> (ImportAndroidHardwareBufferInfoANDROID
    -> ImportAndroidHardwareBufferInfoANDROID -> Bool)
-> Eq ImportAndroidHardwareBufferInfoANDROID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
$c/= :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
== :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
$c== :: ImportAndroidHardwareBufferInfoANDROID
-> ImportAndroidHardwareBufferInfoANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportAndroidHardwareBufferInfoANDROID)
#endif
deriving instance Show ImportAndroidHardwareBufferInfoANDROID

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

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

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

instance Zero ImportAndroidHardwareBufferInfoANDROID where
  zero :: ImportAndroidHardwareBufferInfoANDROID
zero = Ptr AHardwareBuffer -> ImportAndroidHardwareBufferInfoANDROID
ImportAndroidHardwareBufferInfoANDROID
           Ptr AHardwareBuffer
forall a. Zero a => a
zero


-- | VkAndroidHardwareBufferUsageANDROID - Struct containing Android hardware
-- buffer usage flags
--
-- = Description
--
-- The @androidHardwareBufferUsage@ field /must/ include Android hardware
-- buffer usage flags listed in the
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-usage AHardwareBuffer Usage Equivalence>
-- table when the corresponding Vulkan image usage or image creation flags
-- are included in the @usage@ or @flags@ fields of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceImageFormatInfo2'.
-- It /must/ include at least one GPU usage flag
-- (@AHARDWAREBUFFER_USAGE_GPU_*@), even if none of the corresponding
-- Vulkan usages or flags are requested.
--
-- Note
--
-- Requiring at least one GPU usage flag ensures that Android hardware
-- buffer memory will be allocated in a memory pool accessible to the
-- Vulkan implementation, and that specializing the memory layout based on
-- usage flags does not prevent it from being compatible with Vulkan.
-- Implementations /may/ avoid unnecessary restrictions caused by this
-- requirement by using vendor usage flags to indicate that only the Vulkan
-- uses indicated in
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.ImageFormatProperties2'
-- are required.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AndroidHardwareBufferUsageANDROID = AndroidHardwareBufferUsageANDROID
  { -- | @androidHardwareBufferUsage@ returns the Android hardware buffer usage
    -- flags.
    AndroidHardwareBufferUsageANDROID -> Word64
androidHardwareBufferUsage :: Word64 }
  deriving (Typeable, AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
(AndroidHardwareBufferUsageANDROID
 -> AndroidHardwareBufferUsageANDROID -> Bool)
-> (AndroidHardwareBufferUsageANDROID
    -> AndroidHardwareBufferUsageANDROID -> Bool)
-> Eq AndroidHardwareBufferUsageANDROID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
$c/= :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
== :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
$c== :: AndroidHardwareBufferUsageANDROID
-> AndroidHardwareBufferUsageANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferUsageANDROID)
#endif
deriving instance Show AndroidHardwareBufferUsageANDROID

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

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

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

instance Zero AndroidHardwareBufferUsageANDROID where
  zero :: AndroidHardwareBufferUsageANDROID
zero = Word64 -> AndroidHardwareBufferUsageANDROID
AndroidHardwareBufferUsageANDROID
           Word64
forall a. Zero a => a
zero


-- | VkAndroidHardwareBufferPropertiesANDROID - Properties of External Memory
-- Android Hardware Buffers
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkAndroidHardwareBufferPropertiesANDROID-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID'
--
-- -   #VUID-VkAndroidHardwareBufferPropertiesANDROID-pNext-pNext# Each
--     @pNext@ member of any structure (including this one) in the @pNext@
--     chain /must/ be either @NULL@ or a pointer to a valid instance of
--     'AndroidHardwareBufferFormatProperties2ANDROID' or
--     'AndroidHardwareBufferFormatPropertiesANDROID'
--
-- -   #VUID-VkAndroidHardwareBufferPropertiesANDROID-sType-unique# The
--     @sType@ value of each struct in the @pNext@ chain /must/ be unique
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getAndroidHardwareBufferPropertiesANDROID'
data AndroidHardwareBufferPropertiesANDROID (es :: [Type]) = AndroidHardwareBufferPropertiesANDROID
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    AndroidHardwareBufferPropertiesANDROID es -> Chain es
next :: Chain es
  , -- | @allocationSize@ is the size of the external memory
    AndroidHardwareBufferPropertiesANDROID es -> Word64
allocationSize :: DeviceSize
  , -- | @memoryTypeBits@ is a bitmask containing one bit set for every memory
    -- type which the specified Android hardware buffer /can/ be imported as.
    AndroidHardwareBufferPropertiesANDROID es -> Word32
memoryTypeBits :: Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferPropertiesANDROID (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (AndroidHardwareBufferPropertiesANDROID es)

instance Extensible AndroidHardwareBufferPropertiesANDROID where
  extensibleTypeName :: String
extensibleTypeName = String
"AndroidHardwareBufferPropertiesANDROID"
  setNext :: AndroidHardwareBufferPropertiesANDROID ds
-> Chain es -> AndroidHardwareBufferPropertiesANDROID es
setNext AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain ds
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain ds
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} Chain es
next' = AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
AndroidHardwareBufferPropertiesANDROID{$sel:next:AndroidHardwareBufferPropertiesANDROID :: Chain es
next = Chain es
next', Word32
Word64
memoryTypeBits :: Word32
allocationSize :: Word64
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: Word64
..}
  getNext :: AndroidHardwareBufferPropertiesANDROID es -> Chain es
getNext AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain es
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain es
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends AndroidHardwareBufferPropertiesANDROID e => b) -> Maybe b
  extends :: proxy e
-> (Extends AndroidHardwareBufferPropertiesANDROID e => b)
-> Maybe b
extends proxy e
_ Extends AndroidHardwareBufferPropertiesANDROID e => b
f
    | Just e :~: AndroidHardwareBufferFormatProperties2ANDROID
Refl <- (Typeable e,
 Typeable AndroidHardwareBufferFormatProperties2ANDROID) =>
Maybe (e :~: AndroidHardwareBufferFormatProperties2ANDROID)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferFormatProperties2ANDROID = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends AndroidHardwareBufferPropertiesANDROID e => b
f
    | Just e :~: AndroidHardwareBufferFormatPropertiesANDROID
Refl <- (Typeable e,
 Typeable AndroidHardwareBufferFormatPropertiesANDROID) =>
Maybe (e :~: AndroidHardwareBufferFormatPropertiesANDROID)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferFormatPropertiesANDROID = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends AndroidHardwareBufferPropertiesANDROID e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss AndroidHardwareBufferPropertiesANDROID es, PokeChain es) => ToCStruct (AndroidHardwareBufferPropertiesANDROID es) where
  withCStruct :: AndroidHardwareBufferPropertiesANDROID es
-> (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b)
-> IO b
withCStruct AndroidHardwareBufferPropertiesANDROID es
x Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b
f = Int
-> (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b) -> IO b)
-> (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr (AndroidHardwareBufferPropertiesANDROID es)
p -> Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> AndroidHardwareBufferPropertiesANDROID es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p AndroidHardwareBufferPropertiesANDROID es
x (Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b
f Ptr (AndroidHardwareBufferPropertiesANDROID es)
p)
  pokeCStruct :: Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> AndroidHardwareBufferPropertiesANDROID es -> IO b -> IO b
pokeCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p AndroidHardwareBufferPropertiesANDROID{Word32
Word64
Chain es
memoryTypeBits :: Word32
allocationSize :: Word64
next :: Chain es
$sel:memoryTypeBits:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word32
$sel:allocationSize:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Word64
$sel:next:AndroidHardwareBufferPropertiesANDROID :: forall (es :: [*]).
AndroidHardwareBufferPropertiesANDROID es -> Chain es
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (Word64
allocationSize)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
memoryTypeBits)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr (AndroidHardwareBufferPropertiesANDROID es) -> IO b -> IO b
pokeZeroCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (Word64
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss AndroidHardwareBufferPropertiesANDROID es, PeekChain es) => FromCStruct (AndroidHardwareBufferPropertiesANDROID es) where
  peekCStruct :: Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> IO (AndroidHardwareBufferPropertiesANDROID es)
peekCStruct Ptr (AndroidHardwareBufferPropertiesANDROID es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    Word64
allocationSize <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
    Word32
memoryTypeBits <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (AndroidHardwareBufferPropertiesANDROID es)
p Ptr (AndroidHardwareBufferPropertiesANDROID es)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    AndroidHardwareBufferPropertiesANDROID es
-> IO (AndroidHardwareBufferPropertiesANDROID es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AndroidHardwareBufferPropertiesANDROID es
 -> IO (AndroidHardwareBufferPropertiesANDROID es))
-> AndroidHardwareBufferPropertiesANDROID es
-> IO (AndroidHardwareBufferPropertiesANDROID es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
forall (es :: [*]).
Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
AndroidHardwareBufferPropertiesANDROID
             Chain es
next Word64
allocationSize Word32
memoryTypeBits

instance es ~ '[] => Zero (AndroidHardwareBufferPropertiesANDROID es) where
  zero :: AndroidHardwareBufferPropertiesANDROID es
zero = Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
forall (es :: [*]).
Chain es
-> Word64 -> Word32 -> AndroidHardwareBufferPropertiesANDROID es
AndroidHardwareBufferPropertiesANDROID
           ()
           Word64
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkMemoryGetAndroidHardwareBufferInfoANDROID - Structure describing an
-- Android hardware buffer memory export operation
--
-- == Valid Usage
--
-- -   #VUID-VkMemoryGetAndroidHardwareBufferInfoANDROID-handleTypes-01882#
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID'
--     /must/ have been included in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo'::@handleTypes@
--     when @memory@ was created
--
-- -   #VUID-VkMemoryGetAndroidHardwareBufferInfoANDROID-pNext-01883# If
--     the @pNext@ chain of the 'Vulkan.Core10.Memory.MemoryAllocateInfo'
--     used to allocate @memory@ included a
--     'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'
--     with non-@NULL@ @image@ member, then that @image@ /must/ already be
--     bound to @memory@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkMemoryGetAndroidHardwareBufferInfoANDROID-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID'
--
-- -   #VUID-VkMemoryGetAndroidHardwareBufferInfoANDROID-pNext-pNext#
--     @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkMemoryGetAndroidHardwareBufferInfoANDROID-memory-parameter#
--     @memory@ /must/ be a valid 'Vulkan.Core10.Handles.DeviceMemory'
--     handle
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getMemoryAndroidHardwareBufferANDROID'
data MemoryGetAndroidHardwareBufferInfoANDROID = MemoryGetAndroidHardwareBufferInfoANDROID
  { -- | @memory@ is the memory object from which the Android hardware buffer
    -- will be exported.
    MemoryGetAndroidHardwareBufferInfoANDROID -> DeviceMemory
memory :: DeviceMemory }
  deriving (Typeable, MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
(MemoryGetAndroidHardwareBufferInfoANDROID
 -> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool)
-> (MemoryGetAndroidHardwareBufferInfoANDROID
    -> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool)
-> Eq MemoryGetAndroidHardwareBufferInfoANDROID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
$c/= :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
== :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
$c== :: MemoryGetAndroidHardwareBufferInfoANDROID
-> MemoryGetAndroidHardwareBufferInfoANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryGetAndroidHardwareBufferInfoANDROID)
#endif
deriving instance Show MemoryGetAndroidHardwareBufferInfoANDROID

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

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

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

instance Zero MemoryGetAndroidHardwareBufferInfoANDROID where
  zero :: MemoryGetAndroidHardwareBufferInfoANDROID
zero = DeviceMemory -> MemoryGetAndroidHardwareBufferInfoANDROID
MemoryGetAndroidHardwareBufferInfoANDROID
           DeviceMemory
forall a. Zero a => a
zero


-- | VkAndroidHardwareBufferFormatPropertiesANDROID - Structure describing
-- the image format properties of an Android hardware buffer
--
-- = Description
--
-- If the Android hardware buffer has one of the formats listed in the
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-formats Format Equivalence table>,
-- then @format@ /must/ have the equivalent Vulkan format listed in the
-- table. Otherwise, @format@ /may/ be
-- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED', indicating the Android
-- hardware buffer /can/ only be used with an external format.
--
-- The @formatFeatures@ member /must/ include
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_BIT'
-- and at least one of
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT'
-- or
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT',
-- and /should/ include
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
-- and
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT'.
--
-- Note
--
-- The @formatFeatures@ member only indicates the features available when
-- using an
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-external-formats external-format image>
-- created from the Android hardware buffer. Images from Android hardware
-- buffers with a format other than
-- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' are subject to the format
-- capabilities obtained from
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2',
-- and
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
-- with appropriate parameters. These sets of features are independent of
-- each other, e.g. the external format will support sampler Y′CBCR
-- conversion even if the non-external format does not, and writing to
-- non-external format images is possible but writing to external format
-- images is not.
--
-- Android hardware buffers with the same external format /must/ have the
-- same support for
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT',
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT',
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT',
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT',
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT',
-- and
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT'.
-- in @formatFeatures@. Other format features /may/ differ between Android
-- hardware buffers that have the same external format. This allows
-- applications to use the same
-- 'Vulkan.Core11.Handles.SamplerYcbcrConversion' object (and samplers and
-- pipelines created from them) for any Android hardware buffers that have
-- the same external format.
--
-- If @format@ is not 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED', then
-- the value of @samplerYcbcrConversionComponents@ /must/ be valid when
-- used as the @components@ member of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'
-- with that format. If @format@ is
-- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED', all members of
-- @samplerYcbcrConversionComponents@ /must/ be the
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#resources-image-views-identity-mappings identity swizzle>.
--
-- Implementations /may/ not always be able to determine the color model,
-- numerical range, or chroma offsets of the image contents, so the values
-- in 'AndroidHardwareBufferFormatPropertiesANDROID' are only suggestions.
-- Applications /should/ treat these values as sensible defaults to use in
-- the absence of more reliable information obtained through some other
-- means. If the underlying physical device is also usable via OpenGL ES
-- with the
-- <https://www.khronos.org/registry/OpenGL/extensions/OES/OES_EGL_image_external.txt GL_OES_EGL_image_external>
-- extension, the implementation /should/ suggest values that will produce
-- similar sampled values as would be obtained by sampling the same
-- external image via @samplerExternalOES@ in OpenGL ES using equivalent
-- sampler parameters.
--
-- Note
--
-- Since
-- <https://www.khronos.org/registry/OpenGL/extensions/OES/OES_EGL_image_external.txt GL_OES_EGL_image_external>
-- does not require the same sampling and conversion calculations as Vulkan
-- does, achieving identical results between APIs /may/ not be possible on
-- some implementations.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core11.Enums.ChromaLocation.ChromaLocation',
-- 'Vulkan.Core10.ImageView.ComponentMapping',
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FormatFeatureFlags',
-- 'Vulkan.Core11.Enums.SamplerYcbcrModelConversion.SamplerYcbcrModelConversion',
-- 'Vulkan.Core11.Enums.SamplerYcbcrRange.SamplerYcbcrRange',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AndroidHardwareBufferFormatPropertiesANDROID = AndroidHardwareBufferFormatPropertiesANDROID
  { -- | @format@ is the Vulkan format corresponding to the Android hardware
    -- buffer’s format, or 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' if
    -- there is not an equivalent Vulkan format.
    AndroidHardwareBufferFormatPropertiesANDROID -> Format
format :: Format
  , -- | @externalFormat@ is an implementation-defined external format identifier
    -- for use with 'ExternalFormatANDROID'. It /must/ not be zero.
    AndroidHardwareBufferFormatPropertiesANDROID -> Word64
externalFormat :: Word64
  , -- | @formatFeatures@ describes the capabilities of this external format when
    -- used with an image bound to memory imported from @buffer@.
    AndroidHardwareBufferFormatPropertiesANDROID -> FormatFeatureFlags
formatFeatures :: FormatFeatureFlags
  , -- | @samplerYcbcrConversionComponents@ is the component swizzle that
    -- /should/ be used in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatPropertiesANDROID -> ComponentMapping
samplerYcbcrConversionComponents :: ComponentMapping
  , -- | @suggestedYcbcrModel@ is a suggested color model to use in the
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatPropertiesANDROID
-> SamplerYcbcrModelConversion
suggestedYcbcrModel :: SamplerYcbcrModelConversion
  , -- | @suggestedYcbcrRange@ is a suggested numerical value range to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatPropertiesANDROID -> SamplerYcbcrRange
suggestedYcbcrRange :: SamplerYcbcrRange
  , -- | @suggestedXChromaOffset@ is a suggested X chroma offset to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
suggestedXChromaOffset :: ChromaLocation
  , -- | @suggestedYChromaOffset@ is a suggested Y chroma offset to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
suggestedYChromaOffset :: ChromaLocation
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferFormatPropertiesANDROID)
#endif
deriving instance Show AndroidHardwareBufferFormatPropertiesANDROID

instance ToCStruct AndroidHardwareBufferFormatPropertiesANDROID where
  withCStruct :: AndroidHardwareBufferFormatPropertiesANDROID
-> (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b)
-> IO b
withCStruct AndroidHardwareBufferFormatPropertiesANDROID
x Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b
f = Int
-> (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b)
 -> IO b)
-> (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferFormatPropertiesANDROID
p -> Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> AndroidHardwareBufferFormatPropertiesANDROID -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p AndroidHardwareBufferFormatPropertiesANDROID
x (Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b
f Ptr AndroidHardwareBufferFormatPropertiesANDROID
p)
  pokeCStruct :: Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> AndroidHardwareBufferFormatPropertiesANDROID -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p AndroidHardwareBufferFormatPropertiesANDROID{Word64
Format
ComponentMapping
SamplerYcbcrRange
SamplerYcbcrModelConversion
ChromaLocation
FormatFeatureFlags
suggestedYChromaOffset :: ChromaLocation
suggestedXChromaOffset :: ChromaLocation
suggestedYcbcrRange :: SamplerYcbcrRange
suggestedYcbcrModel :: SamplerYcbcrModelConversion
samplerYcbcrConversionComponents :: ComponentMapping
formatFeatures :: FormatFeatureFlags
externalFormat :: Word64
format :: Format
$sel:suggestedYChromaOffset:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
$sel:suggestedXChromaOffset:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ChromaLocation
$sel:suggestedYcbcrRange:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> SamplerYcbcrRange
$sel:suggestedYcbcrModel:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID
-> SamplerYcbcrModelConversion
$sel:samplerYcbcrConversionComponents:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> ComponentMapping
$sel:formatFeatures:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> FormatFeatureFlags
$sel:externalFormat:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> Word64
$sel:format:AndroidHardwareBufferFormatPropertiesANDROID :: AndroidHardwareBufferFormatPropertiesANDROID -> Format
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
format)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
externalFormat)
    Ptr FormatFeatureFlags -> FormatFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
formatFeatures)
    Ptr ComponentMapping -> ComponentMapping -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping)) (ComponentMapping
samplerYcbcrConversionComponents)
    Ptr SamplerYcbcrModelConversion
-> SamplerYcbcrModelConversion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
suggestedYcbcrModel)
    Ptr SamplerYcbcrRange -> SamplerYcbcrRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
suggestedYcbcrRange)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation)) (ChromaLocation
suggestedXChromaOffset)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
suggestedYChromaOffset)
    IO b
f
  cStructSize :: Int
cStructSize = Int
72
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr AndroidHardwareBufferFormatPropertiesANDROID -> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr FormatFeatureFlags -> FormatFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
forall a. Zero a => a
zero)
    Ptr ComponentMapping -> ComponentMapping -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping)) (ComponentMapping
forall a. Zero a => a
zero)
    Ptr SamplerYcbcrModelConversion
-> SamplerYcbcrModelConversion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
forall a. Zero a => a
zero)
    Ptr SamplerYcbcrRange -> SamplerYcbcrRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
forall a. Zero a => a
zero)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation)) (ChromaLocation
forall a. Zero a => a
zero)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AndroidHardwareBufferFormatPropertiesANDROID where
  peekCStruct :: Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> IO AndroidHardwareBufferFormatPropertiesANDROID
peekCStruct Ptr AndroidHardwareBufferFormatPropertiesANDROID
p = do
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
    Word64
externalFormat <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    FormatFeatureFlags
formatFeatures <- Ptr FormatFeatureFlags -> IO FormatFeatureFlags
forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr FormatFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags))
    ComponentMapping
samplerYcbcrConversionComponents <- Ptr ComponentMapping -> IO ComponentMapping
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ComponentMapping ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr ComponentMapping))
    SamplerYcbcrModelConversion
suggestedYcbcrModel <- Ptr SamplerYcbcrModelConversion -> IO SamplerYcbcrModelConversion
forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrModelConversion ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr SamplerYcbcrModelConversion))
    SamplerYcbcrRange
suggestedYcbcrRange <- Ptr SamplerYcbcrRange -> IO SamplerYcbcrRange
forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrRange ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrRange))
    ChromaLocation
suggestedXChromaOffset <- Ptr ChromaLocation -> IO ChromaLocation
forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr ChromaLocation))
    ChromaLocation
suggestedYChromaOffset <- Ptr ChromaLocation -> IO ChromaLocation
forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatPropertiesANDROID
p Ptr AndroidHardwareBufferFormatPropertiesANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation))
    AndroidHardwareBufferFormatPropertiesANDROID
-> IO AndroidHardwareBufferFormatPropertiesANDROID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AndroidHardwareBufferFormatPropertiesANDROID
 -> IO AndroidHardwareBufferFormatPropertiesANDROID)
-> AndroidHardwareBufferFormatPropertiesANDROID
-> IO AndroidHardwareBufferFormatPropertiesANDROID
forall a b. (a -> b) -> a -> b
$ Format
-> Word64
-> FormatFeatureFlags
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatPropertiesANDROID
AndroidHardwareBufferFormatPropertiesANDROID
             Format
format Word64
externalFormat FormatFeatureFlags
formatFeatures ComponentMapping
samplerYcbcrConversionComponents SamplerYcbcrModelConversion
suggestedYcbcrModel SamplerYcbcrRange
suggestedYcbcrRange ChromaLocation
suggestedXChromaOffset ChromaLocation
suggestedYChromaOffset

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

instance Zero AndroidHardwareBufferFormatPropertiesANDROID where
  zero :: AndroidHardwareBufferFormatPropertiesANDROID
zero = Format
-> Word64
-> FormatFeatureFlags
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatPropertiesANDROID
AndroidHardwareBufferFormatPropertiesANDROID
           Format
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           FormatFeatureFlags
forall a. Zero a => a
zero
           ComponentMapping
forall a. Zero a => a
zero
           SamplerYcbcrModelConversion
forall a. Zero a => a
zero
           SamplerYcbcrRange
forall a. Zero a => a
zero
           ChromaLocation
forall a. Zero a => a
zero
           ChromaLocation
forall a. Zero a => a
zero


-- | VkExternalFormatANDROID - Structure containing an Android hardware
-- buffer external format
--
-- = Description
--
-- If @externalFormat@ is zero, the effect is as if the
-- 'ExternalFormatANDROID' structure was not present. Otherwise, the
-- @image@ will have the specified external format.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <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>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ExternalFormatANDROID = ExternalFormatANDROID
  { -- | @externalFormat@ is an implementation-defined identifier for the
    -- external format
    --
    -- #VUID-VkExternalFormatANDROID-externalFormat-01894# @externalFormat@
    -- /must/ be @0@ or a value returned in the @externalFormat@ member of
    -- 'AndroidHardwareBufferFormatPropertiesANDROID' by an earlier call to
    -- 'getAndroidHardwareBufferPropertiesANDROID'
    ExternalFormatANDROID -> Word64
externalFormat :: Word64 }
  deriving (Typeable, ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
(ExternalFormatANDROID -> ExternalFormatANDROID -> Bool)
-> (ExternalFormatANDROID -> ExternalFormatANDROID -> Bool)
-> Eq ExternalFormatANDROID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
$c/= :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
== :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
$c== :: ExternalFormatANDROID -> ExternalFormatANDROID -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExternalFormatANDROID)
#endif
deriving instance Show ExternalFormatANDROID

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

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

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

instance Zero ExternalFormatANDROID where
  zero :: ExternalFormatANDROID
zero = Word64 -> ExternalFormatANDROID
ExternalFormatANDROID
           Word64
forall a. Zero a => a
zero


-- | VkAndroidHardwareBufferFormatProperties2ANDROID - Structure describing
-- the image format properties of an Android hardware buffer
--
-- = Description
--
-- The bits reported in @formatFeatures@ /must/ include the bits reported
-- in the corresponding fields of
-- 'AndroidHardwareBufferFormatPropertiesANDROID'::@formatFeatures@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <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>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_format_feature_flags2 VK_KHR_format_feature_flags2>,
-- 'Vulkan.Core11.Enums.ChromaLocation.ChromaLocation',
-- 'Vulkan.Core10.ImageView.ComponentMapping',
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FormatFeatureFlags2',
-- 'Vulkan.Core11.Enums.SamplerYcbcrModelConversion.SamplerYcbcrModelConversion',
-- 'Vulkan.Core11.Enums.SamplerYcbcrRange.SamplerYcbcrRange',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AndroidHardwareBufferFormatProperties2ANDROID = AndroidHardwareBufferFormatProperties2ANDROID
  { -- | @format@ is the Vulkan format corresponding to the Android hardware
    -- buffer’s format, or 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' if
    -- there is not an equivalent Vulkan format.
    AndroidHardwareBufferFormatProperties2ANDROID -> Format
format :: Format
  , -- | @externalFormat@ is an implementation-defined external format identifier
    -- for use with 'ExternalFormatANDROID'. It /must/ not be zero.
    AndroidHardwareBufferFormatProperties2ANDROID -> Word64
externalFormat :: Word64
  , -- | @formatFeatures@ describes the capabilities of this external format when
    -- used with an image bound to memory imported from @buffer@.
    AndroidHardwareBufferFormatProperties2ANDROID
-> FormatFeatureFlags2
formatFeatures :: FormatFeatureFlags2
  , -- | @samplerYcbcrConversionComponents@ is the component swizzle that
    -- /should/ be used in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatProperties2ANDROID -> ComponentMapping
samplerYcbcrConversionComponents :: ComponentMapping
  , -- | @suggestedYcbcrModel@ is a suggested color model to use in the
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatProperties2ANDROID
-> SamplerYcbcrModelConversion
suggestedYcbcrModel :: SamplerYcbcrModelConversion
  , -- | @suggestedYcbcrRange@ is a suggested numerical value range to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatProperties2ANDROID -> SamplerYcbcrRange
suggestedYcbcrRange :: SamplerYcbcrRange
  , -- | @suggestedXChromaOffset@ is a suggested X chroma offset to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
suggestedXChromaOffset :: ChromaLocation
  , -- | @suggestedYChromaOffset@ is a suggested Y chroma offset to use in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionCreateInfo'.
    AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
suggestedYChromaOffset :: ChromaLocation
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AndroidHardwareBufferFormatProperties2ANDROID)
#endif
deriving instance Show AndroidHardwareBufferFormatProperties2ANDROID

instance ToCStruct AndroidHardwareBufferFormatProperties2ANDROID where
  withCStruct :: AndroidHardwareBufferFormatProperties2ANDROID
-> (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b)
-> IO b
withCStruct AndroidHardwareBufferFormatProperties2ANDROID
x Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b
f = Int
-> (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b)
 -> IO b)
-> (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr AndroidHardwareBufferFormatProperties2ANDROID
p -> Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> AndroidHardwareBufferFormatProperties2ANDROID -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p AndroidHardwareBufferFormatProperties2ANDROID
x (Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b
f Ptr AndroidHardwareBufferFormatProperties2ANDROID
p)
  pokeCStruct :: Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> AndroidHardwareBufferFormatProperties2ANDROID -> IO b -> IO b
pokeCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p AndroidHardwareBufferFormatProperties2ANDROID{Word64
Format
ComponentMapping
SamplerYcbcrRange
SamplerYcbcrModelConversion
ChromaLocation
FormatFeatureFlags2
suggestedYChromaOffset :: ChromaLocation
suggestedXChromaOffset :: ChromaLocation
suggestedYcbcrRange :: SamplerYcbcrRange
suggestedYcbcrModel :: SamplerYcbcrModelConversion
samplerYcbcrConversionComponents :: ComponentMapping
formatFeatures :: FormatFeatureFlags2
externalFormat :: Word64
format :: Format
$sel:suggestedYChromaOffset:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
$sel:suggestedXChromaOffset:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ChromaLocation
$sel:suggestedYcbcrRange:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> SamplerYcbcrRange
$sel:suggestedYcbcrModel:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID
-> SamplerYcbcrModelConversion
$sel:samplerYcbcrConversionComponents:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> ComponentMapping
$sel:formatFeatures:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID
-> FormatFeatureFlags2
$sel:externalFormat:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> Word64
$sel:format:AndroidHardwareBufferFormatProperties2ANDROID :: AndroidHardwareBufferFormatProperties2ANDROID -> Format
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
format)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
externalFormat)
    Ptr FormatFeatureFlags2 -> FormatFeatureFlags2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr FormatFeatureFlags2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2)) (FormatFeatureFlags2
formatFeatures)
    Ptr ComponentMapping -> ComponentMapping -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping)) (ComponentMapping
samplerYcbcrConversionComponents)
    Ptr SamplerYcbcrModelConversion
-> SamplerYcbcrModelConversion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
suggestedYcbcrModel)
    Ptr SamplerYcbcrRange -> SamplerYcbcrRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
suggestedYcbcrRange)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
suggestedXChromaOffset)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation)) (ChromaLocation
suggestedYChromaOffset)
    IO b
f
  cStructSize :: Int
cStructSize = Int
72
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr AndroidHardwareBufferFormatProperties2ANDROID -> IO b -> IO b
pokeZeroCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_2_ANDROID)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr FormatFeatureFlags2 -> FormatFeatureFlags2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr FormatFeatureFlags2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2)) (FormatFeatureFlags2
forall a. Zero a => a
zero)
    Ptr ComponentMapping -> ComponentMapping -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping)) (ComponentMapping
forall a. Zero a => a
zero)
    Ptr SamplerYcbcrModelConversion
-> SamplerYcbcrModelConversion -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion)) (SamplerYcbcrModelConversion
forall a. Zero a => a
zero)
    Ptr SamplerYcbcrRange -> SamplerYcbcrRange -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange)) (SamplerYcbcrRange
forall a. Zero a => a
zero)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation)) (ChromaLocation
forall a. Zero a => a
zero)
    Ptr ChromaLocation -> ChromaLocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation)) (ChromaLocation
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AndroidHardwareBufferFormatProperties2ANDROID where
  peekCStruct :: Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> IO AndroidHardwareBufferFormatProperties2ANDROID
peekCStruct Ptr AndroidHardwareBufferFormatProperties2ANDROID
p = do
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
    Word64
externalFormat <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    FormatFeatureFlags2
formatFeatures <- Ptr FormatFeatureFlags2 -> IO FormatFeatureFlags2
forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags2 ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr FormatFeatureFlags2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr FormatFeatureFlags2))
    ComponentMapping
samplerYcbcrConversionComponents <- Ptr ComponentMapping -> IO ComponentMapping
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ComponentMapping ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ComponentMapping
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ComponentMapping))
    SamplerYcbcrModelConversion
suggestedYcbcrModel <- Ptr SamplerYcbcrModelConversion -> IO SamplerYcbcrModelConversion
forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrModelConversion ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrModelConversion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr SamplerYcbcrModelConversion))
    SamplerYcbcrRange
suggestedYcbcrRange <- Ptr SamplerYcbcrRange -> IO SamplerYcbcrRange
forall a. Storable a => Ptr a -> IO a
peek @SamplerYcbcrRange ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr SamplerYcbcrRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr SamplerYcbcrRange))
    ChromaLocation
suggestedXChromaOffset <- Ptr ChromaLocation -> IO ChromaLocation
forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr ChromaLocation))
    ChromaLocation
suggestedYChromaOffset <- Ptr ChromaLocation -> IO ChromaLocation
forall a. Storable a => Ptr a -> IO a
peek @ChromaLocation ((Ptr AndroidHardwareBufferFormatProperties2ANDROID
p Ptr AndroidHardwareBufferFormatProperties2ANDROID
-> Int -> Ptr ChromaLocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ChromaLocation))
    AndroidHardwareBufferFormatProperties2ANDROID
-> IO AndroidHardwareBufferFormatProperties2ANDROID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AndroidHardwareBufferFormatProperties2ANDROID
 -> IO AndroidHardwareBufferFormatProperties2ANDROID)
-> AndroidHardwareBufferFormatProperties2ANDROID
-> IO AndroidHardwareBufferFormatProperties2ANDROID
forall a b. (a -> b) -> a -> b
$ Format
-> Word64
-> FormatFeatureFlags2
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatProperties2ANDROID
AndroidHardwareBufferFormatProperties2ANDROID
             Format
format Word64
externalFormat FormatFeatureFlags2
formatFeatures ComponentMapping
samplerYcbcrConversionComponents SamplerYcbcrModelConversion
suggestedYcbcrModel SamplerYcbcrRange
suggestedYcbcrRange ChromaLocation
suggestedXChromaOffset ChromaLocation
suggestedYChromaOffset

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

instance Zero AndroidHardwareBufferFormatProperties2ANDROID where
  zero :: AndroidHardwareBufferFormatProperties2ANDROID
zero = Format
-> Word64
-> FormatFeatureFlags2
-> ComponentMapping
-> SamplerYcbcrModelConversion
-> SamplerYcbcrRange
-> ChromaLocation
-> ChromaLocation
-> AndroidHardwareBufferFormatProperties2ANDROID
AndroidHardwareBufferFormatProperties2ANDROID
           Format
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           FormatFeatureFlags2
forall a. Zero a => a
zero
           ComponentMapping
forall a. Zero a => a
zero
           SamplerYcbcrModelConversion
forall a. Zero a => a
zero
           SamplerYcbcrRange
forall a. Zero a => a
zero
           ChromaLocation
forall a. Zero a => a
zero
           ChromaLocation
forall a. Zero a => a
zero


type ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION = 5

-- No documentation found for TopLevel "VK_ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION"
pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: forall a . Integral a => a
pattern $bANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: a
$mANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_SPEC_VERSION = 5


type ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME = "VK_ANDROID_external_memory_android_hardware_buffer"

-- No documentation found for TopLevel "VK_ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME"
pattern ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: a
$mANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
ANDROID_EXTERNAL_MEMORY_ANDROID_HARDWARE_BUFFER_EXTENSION_NAME = "VK_ANDROID_external_memory_android_hardware_buffer"


data AHardwareBuffer