{-# 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 (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 Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.Enums.Format (Format)
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_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)
deriving instance Show ImageViewASTCDecodeModeEXT
instance ToCStruct ImageViewASTCDecodeModeEXT where
withCStruct :: ImageViewASTCDecodeModeEXT
-> (Ptr ImageViewASTCDecodeModeEXT -> IO b) -> IO b
withCStruct x :: ImageViewASTCDecodeModeEXT
x f :: Ptr ImageViewASTCDecodeModeEXT -> IO b
f = Int -> Int -> (Ptr ImageViewASTCDecodeModeEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr ImageViewASTCDecodeModeEXT -> IO b) -> IO b)
-> (Ptr ImageViewASTCDecodeModeEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImageViewASTCDecodeModeEXT
p -> Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO b -> IO b
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 :: Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO b -> IO b
pokeCStruct p :: Ptr ImageViewASTCDecodeModeEXT
p ImageViewASTCDecodeModeEXT{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
decodeMode)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr ImageViewASTCDecodeModeEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImageViewASTCDecodeModeEXT
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageViewASTCDecodeModeEXT where
peekCStruct :: Ptr ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
peekCStruct p :: Ptr ImageViewASTCDecodeModeEXT
p = do
Format
decodeMode <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr ImageViewASTCDecodeModeEXT
p Ptr ImageViewASTCDecodeModeEXT -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format))
ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT)
-> ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
forall a b. (a -> b) -> a -> b
$ Format -> ImageViewASTCDecodeModeEXT
ImageViewASTCDecodeModeEXT
Format
decodeMode
instance Storable ImageViewASTCDecodeModeEXT where
sizeOf :: ImageViewASTCDecodeModeEXT -> Int
sizeOf ~ImageViewASTCDecodeModeEXT
_ = 24
alignment :: ImageViewASTCDecodeModeEXT -> Int
alignment ~ImageViewASTCDecodeModeEXT
_ = 8
peek :: Ptr ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
peek = Ptr ImageViewASTCDecodeModeEXT -> IO ImageViewASTCDecodeModeEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO ()
poke ptr :: Ptr ImageViewASTCDecodeModeEXT
ptr poked :: ImageViewASTCDecodeModeEXT
poked = Ptr ImageViewASTCDecodeModeEXT
-> ImageViewASTCDecodeModeEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewASTCDecodeModeEXT
ptr ImageViewASTCDecodeModeEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewASTCDecodeModeEXT where
zero :: ImageViewASTCDecodeModeEXT
zero = Format -> ImageViewASTCDecodeModeEXT
ImageViewASTCDecodeModeEXT
Format
forall a. Zero a => a
zero
data PhysicalDeviceASTCDecodeFeaturesEXT = PhysicalDeviceASTCDecodeFeaturesEXT
{
PhysicalDeviceASTCDecodeFeaturesEXT -> Bool
decodeModeSharedExponent :: Bool }
deriving (Typeable)
deriving instance Show PhysicalDeviceASTCDecodeFeaturesEXT
instance ToCStruct PhysicalDeviceASTCDecodeFeaturesEXT where
withCStruct :: PhysicalDeviceASTCDecodeFeaturesEXT
-> (Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceASTCDecodeFeaturesEXT
x f :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b
f = Int
-> Int -> (Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p -> Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO b -> IO b
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 :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p PhysicalDeviceASTCDecodeFeaturesEXT{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> 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 PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
decodeModeSharedExponent))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> 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 PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> 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 PhysicalDeviceASTCDecodeFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p = do
Bool32
decodeModeSharedExponent <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceASTCDecodeFeaturesEXT
p Ptr PhysicalDeviceASTCDecodeFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT)
-> PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceASTCDecodeFeaturesEXT
PhysicalDeviceASTCDecodeFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
decodeModeSharedExponent)
instance Storable PhysicalDeviceASTCDecodeFeaturesEXT where
sizeOf :: PhysicalDeviceASTCDecodeFeaturesEXT -> Int
sizeOf ~PhysicalDeviceASTCDecodeFeaturesEXT
_ = 24
alignment :: PhysicalDeviceASTCDecodeFeaturesEXT -> Int
alignment ~PhysicalDeviceASTCDecodeFeaturesEXT
_ = 8
peek :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
peek = Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> IO PhysicalDeviceASTCDecodeFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO ()
poke ptr :: Ptr PhysicalDeviceASTCDecodeFeaturesEXT
ptr poked :: PhysicalDeviceASTCDecodeFeaturesEXT
poked = Ptr PhysicalDeviceASTCDecodeFeaturesEXT
-> PhysicalDeviceASTCDecodeFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceASTCDecodeFeaturesEXT
ptr PhysicalDeviceASTCDecodeFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceASTCDecodeFeaturesEXT where
zero :: PhysicalDeviceASTCDecodeFeaturesEXT
zero = Bool -> PhysicalDeviceASTCDecodeFeaturesEXT
PhysicalDeviceASTCDecodeFeaturesEXT
Bool
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 :: a
$mEXT_ASTC_DECODE_MODE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> 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 :: a
$mEXT_ASTC_DECODE_MODE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_ASTC_DECODE_MODE_EXTENSION_NAME = "VK_EXT_astc_decode_mode"