{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_astc_decode_mode ( ImageViewASTCDecodeModeEXT(..)
, PhysicalDeviceASTCDecodeFeaturesEXT(..)
, EXT_ASTC_DECODE_MODE_SPEC_VERSION
, pattern EXT_ASTC_DECODE_MODE_SPEC_VERSION
, EXT_ASTC_DECODE_MODE_EXTENSION_NAME
, pattern EXT_ASTC_DECODE_MODE_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.Format (Format)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT))
data ImageViewASTCDecodeModeEXT = ImageViewASTCDecodeModeEXT
{
ImageViewASTCDecodeModeEXT -> Format
decodeMode :: Format }
deriving (Typeable, ImageViewASTCDecodeModeEXT -> ImageViewASTCDecodeModeEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewASTCDecodeModeEXT -> ImageViewASTCDecodeModeEXT -> Bool
$c/= :: ImageViewASTCDecodeModeEXT -> ImageViewASTCDecodeModeEXT -> Bool
== :: ImageViewASTCDecodeModeEXT -> ImageViewASTCDecodeModeEXT -> Bool
$c== :: ImageViewASTCDecodeModeEXT -> ImageViewASTCDecodeModeEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewASTCDecodeModeEXT)
#endif
deriving instance Show ImageViewASTCDecodeModeEXT
instance ToCStruct ImageViewASTCDecodeModeEXT where
withCStruct :: forall b.
ImageViewASTCDecodeModeEXT
-> (Ptr ImageViewASTCDecodeModeEXT -> IO b) -> IO b
withCStruct ImageViewASTCDecodeModeEXT
x Ptr ImageViewASTCDecodeModeEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ImageViewASTCDecodeModeEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewASTCDecodeModeEXT
p ImageViewASTCDecodeModeEXT
x (Ptr ImageViewASTCDecodeModeEXT -> IO b
f Ptr ImageViewASTCDecodeModeEXT
p)
pokeCStruct :: forall b.
Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO b -> IO b
pokeCStruct Ptr ImageViewASTCDecodeModeEXT
p ImageViewASTCDecodeModeEXT{Format
decodeMode :: Format
$sel:decodeMode:ImageViewASTCDecodeModeEXT :: ImageViewASTCDecodeModeEXT -> Format
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
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 ImageViewASTCDecodeModeEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (Format
decodeMode)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ImageViewASTCDecodeModeEXT -> IO b -> IO b
pokeZeroCStruct Ptr ImageViewASTCDecodeModeEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
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 ImageViewASTCDecodeModeEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewASTCDecodeModeEXT where
peekCStruct :: Ptr ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
peekCStruct Ptr ImageViewASTCDecodeModeEXT
p = do
Format
decodeMode <- forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr ImageViewASTCDecodeModeEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Format))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Format -> ImageViewASTCDecodeModeEXT
ImageViewASTCDecodeModeEXT
Format
decodeMode
instance Storable ImageViewASTCDecodeModeEXT where
sizeOf :: ImageViewASTCDecodeModeEXT -> Int
sizeOf ~ImageViewASTCDecodeModeEXT
_ = Int
24
alignment :: ImageViewASTCDecodeModeEXT -> Int
alignment ~ImageViewASTCDecodeModeEXT
_ = Int
8
peek :: Ptr ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO ()
poke Ptr ImageViewASTCDecodeModeEXT
ptr ImageViewASTCDecodeModeEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewASTCDecodeModeEXT
ptr ImageViewASTCDecodeModeEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewASTCDecodeModeEXT where
zero :: ImageViewASTCDecodeModeEXT
zero = Format -> ImageViewASTCDecodeModeEXT
ImageViewASTCDecodeModeEXT
forall a. Zero a => a
zero
data PhysicalDeviceASTCDecodeFeaturesEXT = PhysicalDeviceASTCDecodeFeaturesEXT
{
PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
decodeModeSharedExponent :: Bool }
deriving (Typeable, PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
$c/= :: PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
== :: PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
$c== :: PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceASTCDecodeFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceASTCDecodeFeaturesEXT
instance ToCStruct PhysicalDeviceASTCDecodeFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceASTCDecodeFeaturesEXT
-> (Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceASTCDecodeFeaturesEXT
x Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p PhysicalDeviceASTCDecodeFeaturesEXT
x (Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b
f Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p PhysicalDeviceASTCDecodeFeaturesEXT{Bool
decodeModeSharedExponent :: Bool
$sel:decodeModeSharedExponent:PhysicalDeviceASTCDecodeFeaturesEXT :: PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
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 PhysicalDeviceASTCDecodeFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
decodeModeSharedExponent))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
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 PhysicalDeviceASTCDecodeFeaturesEXT
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 PhysicalDeviceASTCDecodeFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
peekCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p = do
Bool32
decodeModeSharedExponent <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
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 -> PhysicalDeviceASTCDecodeFeaturesEXT
PhysicalDeviceASTCDecodeFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
decodeModeSharedExponent)
instance Storable PhysicalDeviceASTCDecodeFeaturesEXT where
sizeOf :: PhysicalDeviceASTCDecodeFeaturesEXT -> Int
sizeOf ~PhysicalDeviceASTCDecodeFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceASTCDecodeFeaturesEXT -> Int
alignment ~PhysicalDeviceASTCDecodeFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceASTCDecodeFeaturesEXT
ptr PhysicalDeviceASTCDecodeFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
ptr PhysicalDeviceASTCDecodeFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceASTCDecodeFeaturesEXT where
zero :: PhysicalDeviceASTCDecodeFeaturesEXT
zero = Bool -> PhysicalDeviceASTCDecodeFeaturesEXT
PhysicalDeviceASTCDecodeFeaturesEXT
forall a. Zero a => a
zero
type EXT_ASTC_DECODE_MODE_SPEC_VERSION = 1
pattern EXT_ASTC_DECODE_MODE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_ASTC_DECODE_MODE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_ASTC_DECODE_MODE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ASTC_DECODE_MODE_SPEC_VERSION = 1
type EXT_ASTC_DECODE_MODE_EXTENSION_NAME = "VK_EXT_astc_decode_mode"
pattern EXT_ASTC_DECODE_MODE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_ASTC_DECODE_MODE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_ASTC_DECODE_MODE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ASTC_DECODE_MODE_EXTENSION_NAME = "VK_EXT_astc_decode_mode"