{-# language CPP #-}
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 (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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
--
-- '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
(TextureLODGatherFormatPropertiesAMD
 -> TextureLODGatherFormatPropertiesAMD -> Bool)
-> (TextureLODGatherFormatPropertiesAMD
    -> TextureLODGatherFormatPropertiesAMD -> Bool)
-> Eq TextureLODGatherFormatPropertiesAMD
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 :: TextureLODGatherFormatPropertiesAMD
-> (Ptr TextureLODGatherFormatPropertiesAMD -> IO b) -> IO b
withCStruct x :: TextureLODGatherFormatPropertiesAMD
x f :: Ptr TextureLODGatherFormatPropertiesAMD -> IO b
f = Int
-> Int -> (Ptr TextureLODGatherFormatPropertiesAMD -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr TextureLODGatherFormatPropertiesAMD -> IO b) -> IO b)
-> (Ptr TextureLODGatherFormatPropertiesAMD -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr TextureLODGatherFormatPropertiesAMD
p -> Ptr TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> IO b -> IO b
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 :: Ptr TextureLODGatherFormatPropertiesAMD
-> TextureLODGatherFormatPropertiesAMD -> IO b -> IO b
pokeCStruct p :: Ptr TextureLODGatherFormatPropertiesAMD
p TextureLODGatherFormatPropertiesAMD{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
supportsTextureGatherLODBiasAMD))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr TextureLODGatherFormatPropertiesAMD -> IO b -> IO b
pokeZeroCStruct p :: Ptr TextureLODGatherFormatPropertiesAMD
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TextureLODGatherFormatPropertiesAMD
p Ptr TextureLODGatherFormatPropertiesAMD -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

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

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

instance Zero TextureLODGatherFormatPropertiesAMD where
  zero :: TextureLODGatherFormatPropertiesAMD
zero = Bool -> TextureLODGatherFormatPropertiesAMD
TextureLODGatherFormatPropertiesAMD
           Bool
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 :: a
$mAMD_TEXTURE_GATHER_BIAS_LOD_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> 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 :: a
$mAMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
AMD_TEXTURE_GATHER_BIAS_LOD_EXTENSION_NAME = "VK_AMD_texture_gather_bias_lod"