{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_4444_formats ( PhysicalDevice4444FormatsFeaturesEXT(..)
, EXT_4444_FORMATS_SPEC_VERSION
, pattern EXT_4444_FORMATS_SPEC_VERSION
, EXT_4444_FORMATS_EXTENSION_NAME
, pattern EXT_4444_FORMATS_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytesAligned)
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_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT))
data PhysicalDevice4444FormatsFeaturesEXT = PhysicalDevice4444FormatsFeaturesEXT
{
PhysicalDevice4444FormatsFeaturesEXT -> Bool
formatA4R4G4B4 :: Bool
,
PhysicalDevice4444FormatsFeaturesEXT -> Bool
formatA4B4G4R4 :: Bool
}
deriving (Typeable, PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
(PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool)
-> (PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool)
-> Eq PhysicalDevice4444FormatsFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
$c/= :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
== :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
$c== :: PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevice4444FormatsFeaturesEXT)
#endif
deriving instance Show PhysicalDevice4444FormatsFeaturesEXT
instance ToCStruct PhysicalDevice4444FormatsFeaturesEXT where
withCStruct :: PhysicalDevice4444FormatsFeaturesEXT
-> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDevice4444FormatsFeaturesEXT
x f :: Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevice4444FormatsFeaturesEXT
p -> Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice4444FormatsFeaturesEXT
p PhysicalDevice4444FormatsFeaturesEXT
x (Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b
f Ptr PhysicalDevice4444FormatsFeaturesEXT
p)
pokeCStruct :: Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDevice4444FormatsFeaturesEXT
p PhysicalDevice4444FormatsFeaturesEXT{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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 PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
formatA4R4G4B4))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
formatA4B4G4R4))
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PhysicalDevice4444FormatsFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevice4444FormatsFeaturesEXT
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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 PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> 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))
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevice4444FormatsFeaturesEXT where
peekCStruct :: Ptr PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT
peekCStruct p :: Ptr PhysicalDevice4444FormatsFeaturesEXT
p = do
Bool32
formatA4R4G4B4 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
Bool32
formatA4B4G4R4 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice4444FormatsFeaturesEXT
p Ptr PhysicalDevice4444FormatsFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT)
-> PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> PhysicalDevice4444FormatsFeaturesEXT
PhysicalDevice4444FormatsFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
formatA4R4G4B4) (Bool32 -> Bool
bool32ToBool Bool32
formatA4B4G4R4)
instance Storable PhysicalDevice4444FormatsFeaturesEXT where
sizeOf :: PhysicalDevice4444FormatsFeaturesEXT -> Int
sizeOf ~PhysicalDevice4444FormatsFeaturesEXT
_ = 24
alignment :: PhysicalDevice4444FormatsFeaturesEXT -> Int
alignment ~PhysicalDevice4444FormatsFeaturesEXT
_ = 8
peek :: Ptr PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT
peek = Ptr PhysicalDevice4444FormatsFeaturesEXT
-> IO PhysicalDevice4444FormatsFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO ()
poke ptr :: Ptr PhysicalDevice4444FormatsFeaturesEXT
ptr poked :: PhysicalDevice4444FormatsFeaturesEXT
poked = Ptr PhysicalDevice4444FormatsFeaturesEXT
-> PhysicalDevice4444FormatsFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice4444FormatsFeaturesEXT
ptr PhysicalDevice4444FormatsFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevice4444FormatsFeaturesEXT where
zero :: PhysicalDevice4444FormatsFeaturesEXT
zero = Bool -> Bool -> PhysicalDevice4444FormatsFeaturesEXT
PhysicalDevice4444FormatsFeaturesEXT
Bool
forall a. Zero a => a
zero
Bool
forall a. Zero a => a
zero
type EXT_4444_FORMATS_SPEC_VERSION = 1
pattern EXT_4444_FORMATS_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_4444_FORMATS_SPEC_VERSION :: a
$mEXT_4444_FORMATS_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_4444_FORMATS_SPEC_VERSION = 1
type EXT_4444_FORMATS_EXTENSION_NAME = "VK_EXT_4444_formats"
pattern EXT_4444_FORMATS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_4444_FORMATS_EXTENSION_NAME :: a
$mEXT_4444_FORMATS_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_4444_FORMATS_EXTENSION_NAME = "VK_EXT_4444_formats"