{-# language CPP #-}
-- | = Name
--
-- VK_AMD_texture_gather_bias_lod - device extension
--
-- == VK_AMD_texture_gather_bias_lod
--
-- [__Name String__]
--     @VK_AMD_texture_gather_bias_lod@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     42
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@ to be enabled
--         for any device-level functionality
--
-- [__Contact__]
--
--     -   Rex Xu
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_AMD_texture_gather_bias_lod] @amdrexu%0A*Here describe the issue or question you have about the VK_AMD_texture_gather_bias_lod extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2017-03-21
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/AMD/SPV_AMD_texture_gather_bias_lod.html SPV_AMD_texture_gather_bias_lod>
--
--     -   This extension provides API support for
--         <https://registry.khronos.org/OpenGL/extensions/AMD/AMD_texture_gather_bias_lod.txt GL_AMD_texture_gather_bias_lod>
--
-- [__Contributors__]
--
--     -   Dominik Witczak, AMD
--
--     -   Daniel Rakos, AMD
--
--     -   Graham Sellers, AMD
--
--     -   Matthaeus G. Chajdas, AMD
--
--     -   Qun Lin, AMD
--
--     -   Rex Xu, AMD
--
--     -   Timothy Lottes, AMD
--
-- == Description
--
-- This extension adds two related features.
--
-- Firstly, support for the following SPIR-V extension in Vulkan is added:
--
-- -   @SPV_AMD_texture_gather_bias_lod@
--
-- Secondly, the extension allows the application to query which formats
-- can be used together with the new function prototypes introduced by the
-- SPIR-V extension.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.ImageFormatProperties2':
--
--     -   'TextureLODGatherFormatPropertiesAMD'
--
-- == New Enum Constants
--
-- -   'AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME'
--
-- -   'AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD'
--
-- == New SPIR-V Capabilities
--
-- -   <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#spirvenv-capabilities-table-ImageGatherBiasLodAMD ImageGatherBiasLodAMD>
--
-- == Examples
--
-- > struct VkTextureLODGatherFormatPropertiesAMD
-- > {
-- >     VkStructureType sType;
-- >     const void*     pNext;
-- >     VkBool32        supportsTextureGatherLODBiasAMD;
-- > };
-- >
-- > // ----------------------------------------------------------------------------------------
-- > // How to detect if an image format can be used with the new function prototypes.
-- > VkPhysicalDeviceImageFormatInfo2   formatInfo;
-- > VkImageFormatProperties2           formatProps;
-- > VkTextureLODGatherFormatPropertiesAMD textureLODGatherSupport;
-- >
-- > textureLODGatherSupport.sType = VK_STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD;
-- > textureLODGatherSupport.pNext = nullptr;
-- >
-- > formatInfo.sType  = VK_STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2;
-- > formatInfo.pNext  = nullptr;
-- > formatInfo.format = ...;
-- > formatInfo.type   = ...;
-- > formatInfo.tiling = ...;
-- > formatInfo.usage  = ...;
-- > formatInfo.flags  = ...;
-- >
-- > formatProps.sType = VK_STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2;
-- > formatProps.pNext = &textureLODGatherSupport;
-- >
-- > vkGetPhysicalDeviceImageFormatProperties2(physical_device, &formatInfo, &formatProps);
-- >
-- > if (textureLODGatherSupport.supportsTextureGatherLODBiasAMD == VK_TRUE)
-- > {
-- >     // physical device supports SPV_AMD_texture_gather_bias_lod for the specified
-- >     // format configuration.
-- > }
-- > else
-- > {
-- >     // physical device does not support SPV_AMD_texture_gather_bias_lod for the
-- >     // specified format configuration.
-- > }
--
-- == Version History
--
-- -   Revision 1, 2017-03-21 (Dominik Witczak)
--
--     -   Initial draft
--
-- == See Also
--
-- 'TextureLODGatherFormatPropertiesAMD'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_AMD_texture_gather_bias_lod Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_AMD_texture_gather_bias_lod  ( TextureLODGatherFormatPropertiesAMD(..)
                                                         , AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION
                                                         , pattern AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION
                                                         , AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME
                                                         , pattern AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME
                                                         ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD))
-- | VkTextureLODGatherFormatPropertiesAMD - Structure informing whether or
-- not texture gather bias\/LOD functionality is supported for a given
-- image format and a given physical device.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_AMD_texture_gather_bias_lod VK_AMD_texture_gather_bias_lod>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data TextureLODGatherFormatPropertiesAMD = TextureLODGatherFormatPropertiesAMD
  { -- | @supportsTextureGatherLODBiasAMD@ tells if the image format can be used
    -- with texture gather bias\/LOD functions, as introduced by the
    -- @VK_AMD_texture_gather_bias_lod@ extension. This field is set by the
    -- implementation. User-specified value is ignored.
    TextureLODGatherFormatPropertiesAMD -> Bool
supportsTextureGatherLODBiasAMD :: Bool }
  deriving (Typeable, TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> Bool
$c/= :: TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> Bool
== :: TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> Bool
$c== :: TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (TextureLODGatherFormatPropertiesAMD)
#endif
deriving instance Show TextureLODGatherFormatPropertiesAMD

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

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

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

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


type AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION"
pattern AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION :: forall a . Integral a => a
pattern $bAMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION :: forall a. Integral a => a
$mAMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION = 1


type AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME = "VK_AMD_texture_gather_bias_lod"

-- No documentation found for TopLevel "VK_AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME"
pattern AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bAMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mAMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME = "VK_AMD_texture_gather_bias_lod"