{-# 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 (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))
data TextureLODGatherFormatPropertiesAMD = TextureLODGatherFormatPropertiesAMD
{
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
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"
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"