{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_image_drm_format_modifier ( getImageDrmFormatModifierPropertiesEXT
, DrmFormatModifierPropertiesListEXT(..)
, DrmFormatModifierPropertiesEXT(..)
, PhysicalDeviceImageDrmFormatModifierInfoEXT(..)
, ImageDrmFormatModifierListCreateInfoEXT(..)
, ImageDrmFormatModifierExplicitCreateInfoEXT(..)
, ImageDrmFormatModifierPropertiesEXT(..)
, DrmFormatModifierPropertiesList2EXT(..)
, DrmFormatModifierProperties2EXT(..)
, EXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION
, pattern EXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION
, EXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME
, pattern EXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetImageDrmFormatModifierPropertiesEXT))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.Core13.Enums.FormatFeatureFlags2 (FormatFeatureFlags2)
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SharingMode (SharingMode)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Image (SubresourceLayout)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_2_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_EXPLICIT_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_LIST_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_DRM_FORMAT_MODIFIER_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetImageDrmFormatModifierPropertiesEXT
:: FunPtr (Ptr Device_T -> Image -> Ptr ImageDrmFormatModifierPropertiesEXT -> IO Result) -> Ptr Device_T -> Image -> Ptr ImageDrmFormatModifierPropertiesEXT -> IO Result
getImageDrmFormatModifierPropertiesEXT :: forall io
. (MonadIO io)
=>
Device
->
Image
-> io (ImageDrmFormatModifierPropertiesEXT)
getImageDrmFormatModifierPropertiesEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> Image -> io ImageDrmFormatModifierPropertiesEXT
getImageDrmFormatModifierPropertiesEXT Device
device Image
image = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetImageDrmFormatModifierPropertiesEXTPtr :: FunPtr
(Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result)
vkGetImageDrmFormatModifierPropertiesEXTPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result)
pVkGetImageDrmFormatModifierPropertiesEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result)
vkGetImageDrmFormatModifierPropertiesEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetImageDrmFormatModifierPropertiesEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetImageDrmFormatModifierPropertiesEXT' :: Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result
vkGetImageDrmFormatModifierPropertiesEXT' = FunPtr
(Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result)
-> Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result
mkVkGetImageDrmFormatModifierPropertiesEXT FunPtr
(Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result)
vkGetImageDrmFormatModifierPropertiesEXTPtr
"pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
pPProperties <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @ImageDrmFormatModifierPropertiesEXT)
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetImageDrmFormatModifierPropertiesEXT" (Ptr Device_T
-> Image
-> ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO Result
vkGetImageDrmFormatModifierPropertiesEXT'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(Image
image)
("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
pPProperties))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
ImageDrmFormatModifierPropertiesEXT
pProperties <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageDrmFormatModifierPropertiesEXT "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
pPProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (ImageDrmFormatModifierPropertiesEXT
pProperties)
data DrmFormatModifierPropertiesListEXT = DrmFormatModifierPropertiesListEXT
{
DrmFormatModifierPropertiesListEXT -> Word32
drmFormatModifierCount :: Word32
,
DrmFormatModifierPropertiesListEXT
-> Ptr DrmFormatModifierPropertiesEXT
drmFormatModifierProperties :: Ptr DrmFormatModifierPropertiesEXT
}
deriving (Typeable, DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> Bool
$c/= :: DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> Bool
== :: DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> Bool
$c== :: DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrmFormatModifierPropertiesListEXT)
#endif
deriving instance Show DrmFormatModifierPropertiesListEXT
instance ToCStruct DrmFormatModifierPropertiesListEXT where
withCStruct :: forall b.
DrmFormatModifierPropertiesListEXT
-> (Ptr DrmFormatModifierPropertiesListEXT -> IO b) -> IO b
withCStruct DrmFormatModifierPropertiesListEXT
x Ptr DrmFormatModifierPropertiesListEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr DrmFormatModifierPropertiesListEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesListEXT
p DrmFormatModifierPropertiesListEXT
x (Ptr DrmFormatModifierPropertiesListEXT -> IO b
f Ptr DrmFormatModifierPropertiesListEXT
p)
pokeCStruct :: forall b.
Ptr DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesListEXT
p DrmFormatModifierPropertiesListEXT{Word32
Ptr DrmFormatModifierPropertiesEXT
drmFormatModifierProperties :: Ptr DrmFormatModifierPropertiesEXT
drmFormatModifierCount :: Word32
$sel:drmFormatModifierProperties:DrmFormatModifierPropertiesListEXT :: DrmFormatModifierPropertiesListEXT
-> Ptr DrmFormatModifierPropertiesEXT
$sel:drmFormatModifierCount:DrmFormatModifierPropertiesListEXT :: DrmFormatModifierPropertiesListEXT -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesListEXT
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 DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
drmFormatModifierCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DrmFormatModifierPropertiesEXT))) (Ptr DrmFormatModifierPropertiesEXT
drmFormatModifierProperties)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DrmFormatModifierPropertiesListEXT -> IO b -> IO b
pokeZeroCStruct Ptr DrmFormatModifierPropertiesListEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct DrmFormatModifierPropertiesListEXT where
peekCStruct :: Ptr DrmFormatModifierPropertiesListEXT
-> IO DrmFormatModifierPropertiesListEXT
peekCStruct Ptr DrmFormatModifierPropertiesListEXT
p = do
Word32
drmFormatModifierCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr DrmFormatModifierPropertiesEXT
pDrmFormatModifierProperties <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DrmFormatModifierPropertiesEXT) ((Ptr DrmFormatModifierPropertiesListEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DrmFormatModifierPropertiesEXT)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Ptr DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesListEXT
DrmFormatModifierPropertiesListEXT
Word32
drmFormatModifierCount Ptr DrmFormatModifierPropertiesEXT
pDrmFormatModifierProperties
instance Storable DrmFormatModifierPropertiesListEXT where
sizeOf :: DrmFormatModifierPropertiesListEXT -> Int
sizeOf ~DrmFormatModifierPropertiesListEXT
_ = Int
32
alignment :: DrmFormatModifierPropertiesListEXT -> Int
alignment ~DrmFormatModifierPropertiesListEXT
_ = Int
8
peek :: Ptr DrmFormatModifierPropertiesListEXT
-> IO DrmFormatModifierPropertiesListEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrmFormatModifierPropertiesListEXT
-> DrmFormatModifierPropertiesListEXT -> IO ()
poke Ptr DrmFormatModifierPropertiesListEXT
ptr DrmFormatModifierPropertiesListEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesListEXT
ptr DrmFormatModifierPropertiesListEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrmFormatModifierPropertiesListEXT where
zero :: DrmFormatModifierPropertiesListEXT
zero = Word32
-> Ptr DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesListEXT
DrmFormatModifierPropertiesListEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data DrmFormatModifierPropertiesEXT = DrmFormatModifierPropertiesEXT
{
DrmFormatModifierPropertiesEXT -> Word64
drmFormatModifier :: Word64
,
DrmFormatModifierPropertiesEXT -> Word32
drmFormatModifierPlaneCount :: Word32
,
DrmFormatModifierPropertiesEXT -> FormatFeatureFlags
drmFormatModifierTilingFeatures :: FormatFeatureFlags
}
deriving (Typeable, DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> Bool
$c/= :: DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> Bool
== :: DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> Bool
$c== :: DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrmFormatModifierPropertiesEXT)
#endif
deriving instance Show DrmFormatModifierPropertiesEXT
instance ToCStruct DrmFormatModifierPropertiesEXT where
withCStruct :: forall b.
DrmFormatModifierPropertiesEXT
-> (Ptr DrmFormatModifierPropertiesEXT -> IO b) -> IO b
withCStruct DrmFormatModifierPropertiesEXT
x Ptr DrmFormatModifierPropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 forall a b. (a -> b) -> a -> b
$ \Ptr DrmFormatModifierPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesEXT
p DrmFormatModifierPropertiesEXT
x (Ptr DrmFormatModifierPropertiesEXT -> IO b
f Ptr DrmFormatModifierPropertiesEXT
p)
pokeCStruct :: forall b.
Ptr DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesEXT
p DrmFormatModifierPropertiesEXT{Word32
Word64
FormatFeatureFlags
drmFormatModifierTilingFeatures :: FormatFeatureFlags
drmFormatModifierPlaneCount :: Word32
drmFormatModifier :: Word64
$sel:drmFormatModifierTilingFeatures:DrmFormatModifierPropertiesEXT :: DrmFormatModifierPropertiesEXT -> FormatFeatureFlags
$sel:drmFormatModifierPlaneCount:DrmFormatModifierPropertiesEXT :: DrmFormatModifierPropertiesEXT -> Word32
$sel:drmFormatModifier:DrmFormatModifierPropertiesEXT :: DrmFormatModifierPropertiesEXT -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64)) (Word64
drmFormatModifier)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
drmFormatModifierPlaneCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr FormatFeatureFlags)) (FormatFeatureFlags
drmFormatModifierTilingFeatures)
IO b
f
cStructSize :: Int
cStructSize = Int
16
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DrmFormatModifierPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr DrmFormatModifierPropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr FormatFeatureFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DrmFormatModifierPropertiesEXT where
peekCStruct :: Ptr DrmFormatModifierPropertiesEXT
-> IO DrmFormatModifierPropertiesEXT
peekCStruct Ptr DrmFormatModifierPropertiesEXT
p = do
Word64
drmFormatModifier <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64))
Word32
drmFormatModifierPlaneCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
FormatFeatureFlags
drmFormatModifierTilingFeatures <- forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags ((Ptr DrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr FormatFeatureFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64
-> Word32 -> FormatFeatureFlags -> DrmFormatModifierPropertiesEXT
DrmFormatModifierPropertiesEXT
Word64
drmFormatModifier
Word32
drmFormatModifierPlaneCount
FormatFeatureFlags
drmFormatModifierTilingFeatures
instance Storable DrmFormatModifierPropertiesEXT where
sizeOf :: DrmFormatModifierPropertiesEXT -> Int
sizeOf ~DrmFormatModifierPropertiesEXT
_ = Int
16
alignment :: DrmFormatModifierPropertiesEXT -> Int
alignment ~DrmFormatModifierPropertiesEXT
_ = Int
8
peek :: Ptr DrmFormatModifierPropertiesEXT
-> IO DrmFormatModifierPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrmFormatModifierPropertiesEXT
-> DrmFormatModifierPropertiesEXT -> IO ()
poke Ptr DrmFormatModifierPropertiesEXT
ptr DrmFormatModifierPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesEXT
ptr DrmFormatModifierPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrmFormatModifierPropertiesEXT where
zero :: DrmFormatModifierPropertiesEXT
zero = Word64
-> Word32 -> FormatFeatureFlags -> DrmFormatModifierPropertiesEXT
DrmFormatModifierPropertiesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceImageDrmFormatModifierInfoEXT = PhysicalDeviceImageDrmFormatModifierInfoEXT
{
PhysicalDeviceImageDrmFormatModifierInfoEXT -> Word64
drmFormatModifier :: Word64
,
PhysicalDeviceImageDrmFormatModifierInfoEXT -> SharingMode
sharingMode :: SharingMode
,
PhysicalDeviceImageDrmFormatModifierInfoEXT -> Vector Word32
queueFamilyIndices :: Vector Word32
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageDrmFormatModifierInfoEXT)
#endif
deriving instance Show PhysicalDeviceImageDrmFormatModifierInfoEXT
instance ToCStruct PhysicalDeviceImageDrmFormatModifierInfoEXT where
withCStruct :: forall b.
PhysicalDeviceImageDrmFormatModifierInfoEXT
-> (Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceImageDrmFormatModifierInfoEXT
x Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p PhysicalDeviceImageDrmFormatModifierInfoEXT
x (Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT -> IO b
f Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
-> PhysicalDeviceImageDrmFormatModifierInfoEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p PhysicalDeviceImageDrmFormatModifierInfoEXT{Word64
Vector Word32
SharingMode
queueFamilyIndices :: Vector Word32
sharingMode :: SharingMode
drmFormatModifier :: Word64
$sel:queueFamilyIndices:PhysicalDeviceImageDrmFormatModifierInfoEXT :: PhysicalDeviceImageDrmFormatModifierInfoEXT -> Vector Word32
$sel:sharingMode:PhysicalDeviceImageDrmFormatModifierInfoEXT :: PhysicalDeviceImageDrmFormatModifierInfoEXT -> SharingMode
$sel:drmFormatModifier:PhysicalDeviceImageDrmFormatModifierInfoEXT :: PhysicalDeviceImageDrmFormatModifierInfoEXT -> Word64
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_DRM_FORMAT_MODIFIER_INFO_EXT)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
drmFormatModifier)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SharingMode)) (SharingMode
sharingMode)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word32
queueFamilyIndices)) :: Word32))
Ptr Word32
pPQueueFamilyIndices' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Word32 ((forall a. Vector a -> Int
Data.Vector.length (Vector Word32
queueFamilyIndices)) forall a. Num a => a -> a -> a
* Int
4)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPQueueFamilyIndices' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
queueFamilyIndices)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Word32))) (Ptr Word32
pPQueueFamilyIndices')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_DRM_FORMAT_MODIFIER_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
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 PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SharingMode)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceImageDrmFormatModifierInfoEXT where
peekCStruct :: Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
-> IO PhysicalDeviceImageDrmFormatModifierInfoEXT
peekCStruct Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p = do
Word64
drmFormatModifier <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
SharingMode
sharingMode <- forall a. Storable a => Ptr a -> IO a
peek @SharingMode ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SharingMode))
Word32
queueFamilyIndexCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
Ptr Word32
pQueueFamilyIndices <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr PhysicalDeviceImageDrmFormatModifierInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Word32)))
Vector Word32
pQueueFamilyIndices' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
queueFamilyIndexCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pQueueFamilyIndices forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64
-> SharingMode
-> Vector Word32
-> PhysicalDeviceImageDrmFormatModifierInfoEXT
PhysicalDeviceImageDrmFormatModifierInfoEXT
Word64
drmFormatModifier SharingMode
sharingMode Vector Word32
pQueueFamilyIndices'
instance Zero PhysicalDeviceImageDrmFormatModifierInfoEXT where
zero :: PhysicalDeviceImageDrmFormatModifierInfoEXT
zero = Word64
-> SharingMode
-> Vector Word32
-> PhysicalDeviceImageDrmFormatModifierInfoEXT
PhysicalDeviceImageDrmFormatModifierInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Monoid a => a
mempty
data ImageDrmFormatModifierListCreateInfoEXT = ImageDrmFormatModifierListCreateInfoEXT
{
ImageDrmFormatModifierListCreateInfoEXT -> Vector Word64
drmFormatModifiers :: Vector Word64 }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageDrmFormatModifierListCreateInfoEXT)
#endif
deriving instance Show ImageDrmFormatModifierListCreateInfoEXT
instance ToCStruct ImageDrmFormatModifierListCreateInfoEXT where
withCStruct :: forall b.
ImageDrmFormatModifierListCreateInfoEXT
-> (Ptr ImageDrmFormatModifierListCreateInfoEXT -> IO b) -> IO b
withCStruct ImageDrmFormatModifierListCreateInfoEXT
x Ptr ImageDrmFormatModifierListCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr ImageDrmFormatModifierListCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageDrmFormatModifierListCreateInfoEXT
p ImageDrmFormatModifierListCreateInfoEXT
x (Ptr ImageDrmFormatModifierListCreateInfoEXT -> IO b
f Ptr ImageDrmFormatModifierListCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr ImageDrmFormatModifierListCreateInfoEXT
-> ImageDrmFormatModifierListCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr ImageDrmFormatModifierListCreateInfoEXT
p ImageDrmFormatModifierListCreateInfoEXT{Vector Word64
drmFormatModifiers :: Vector Word64
$sel:drmFormatModifiers:ImageDrmFormatModifierListCreateInfoEXT :: ImageDrmFormatModifierListCreateInfoEXT -> Vector Word64
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_LIST_CREATE_INFO_EXT)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word64
drmFormatModifiers)) :: Word32))
Ptr Word64
pPDrmFormatModifiers' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Word64 ((forall a. Vector a -> Int
Data.Vector.length (Vector Word64
drmFormatModifiers)) forall a. Num a => a -> a -> a
* Int
8)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Word64
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word64
pPDrmFormatModifiers' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64) (Word64
e)) (Vector Word64
drmFormatModifiers)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word64))) (Ptr Word64
pPDrmFormatModifiers')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr ImageDrmFormatModifierListCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr ImageDrmFormatModifierListCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_LIST_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct ImageDrmFormatModifierListCreateInfoEXT where
peekCStruct :: Ptr ImageDrmFormatModifierListCreateInfoEXT
-> IO ImageDrmFormatModifierListCreateInfoEXT
peekCStruct Ptr ImageDrmFormatModifierListCreateInfoEXT
p = do
Word32
drmFormatModifierCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr Word64
pDrmFormatModifiers <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word64) ((Ptr ImageDrmFormatModifierListCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Word64)))
Vector Word64
pDrmFormatModifiers' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
drmFormatModifierCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr Word64
pDrmFormatModifiers forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector Word64 -> ImageDrmFormatModifierListCreateInfoEXT
ImageDrmFormatModifierListCreateInfoEXT
Vector Word64
pDrmFormatModifiers'
instance Zero ImageDrmFormatModifierListCreateInfoEXT where
zero :: ImageDrmFormatModifierListCreateInfoEXT
zero = Vector Word64 -> ImageDrmFormatModifierListCreateInfoEXT
ImageDrmFormatModifierListCreateInfoEXT
forall a. Monoid a => a
mempty
data ImageDrmFormatModifierExplicitCreateInfoEXT = ImageDrmFormatModifierExplicitCreateInfoEXT
{
ImageDrmFormatModifierExplicitCreateInfoEXT -> Word64
drmFormatModifier :: Word64
,
ImageDrmFormatModifierExplicitCreateInfoEXT
-> Vector SubresourceLayout
planeLayouts :: Vector SubresourceLayout
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageDrmFormatModifierExplicitCreateInfoEXT)
#endif
deriving instance Show ImageDrmFormatModifierExplicitCreateInfoEXT
instance ToCStruct ImageDrmFormatModifierExplicitCreateInfoEXT where
withCStruct :: forall b.
ImageDrmFormatModifierExplicitCreateInfoEXT
-> (Ptr ImageDrmFormatModifierExplicitCreateInfoEXT -> IO b)
-> IO b
withCStruct ImageDrmFormatModifierExplicitCreateInfoEXT
x Ptr ImageDrmFormatModifierExplicitCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p ImageDrmFormatModifierExplicitCreateInfoEXT
x (Ptr ImageDrmFormatModifierExplicitCreateInfoEXT -> IO b
f Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
-> ImageDrmFormatModifierExplicitCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p ImageDrmFormatModifierExplicitCreateInfoEXT{Word64
Vector SubresourceLayout
planeLayouts :: Vector SubresourceLayout
drmFormatModifier :: Word64
$sel:planeLayouts:ImageDrmFormatModifierExplicitCreateInfoEXT :: ImageDrmFormatModifierExplicitCreateInfoEXT
-> Vector SubresourceLayout
$sel:drmFormatModifier:ImageDrmFormatModifierExplicitCreateInfoEXT :: ImageDrmFormatModifierExplicitCreateInfoEXT -> Word64
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_EXPLICIT_CREATE_INFO_EXT)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
drmFormatModifier)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector SubresourceLayout
planeLayouts)) :: Word32))
Ptr SubresourceLayout
pPPlaneLayouts' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @SubresourceLayout ((forall a. Vector a -> Int
Data.Vector.length (Vector SubresourceLayout
planeLayouts)) forall a. Num a => a -> a -> a
* Int
40)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i SubresourceLayout
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SubresourceLayout
pPPlaneLayouts' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
40 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubresourceLayout) (SubresourceLayout
e)) (Vector SubresourceLayout
planeLayouts)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr SubresourceLayout))) (Ptr SubresourceLayout
pPPlaneLayouts')
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr ImageDrmFormatModifierExplicitCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_EXPLICIT_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
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 ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageDrmFormatModifierExplicitCreateInfoEXT where
peekCStruct :: Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
-> IO ImageDrmFormatModifierExplicitCreateInfoEXT
peekCStruct Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p = do
Word64
drmFormatModifier <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
Word32
drmFormatModifierPlaneCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
Ptr SubresourceLayout
pPlaneLayouts <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubresourceLayout) ((Ptr ImageDrmFormatModifierExplicitCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr SubresourceLayout)))
Vector SubresourceLayout
pPlaneLayouts' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
drmFormatModifierPlaneCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubresourceLayout ((Ptr SubresourceLayout
pPlaneLayouts forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
40 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubresourceLayout)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64
-> Vector SubresourceLayout
-> ImageDrmFormatModifierExplicitCreateInfoEXT
ImageDrmFormatModifierExplicitCreateInfoEXT
Word64
drmFormatModifier Vector SubresourceLayout
pPlaneLayouts'
instance Zero ImageDrmFormatModifierExplicitCreateInfoEXT where
zero :: ImageDrmFormatModifierExplicitCreateInfoEXT
zero = Word64
-> Vector SubresourceLayout
-> ImageDrmFormatModifierExplicitCreateInfoEXT
ImageDrmFormatModifierExplicitCreateInfoEXT
forall a. Zero a => a
zero
forall a. Monoid a => a
mempty
data ImageDrmFormatModifierPropertiesEXT = ImageDrmFormatModifierPropertiesEXT
{
ImageDrmFormatModifierPropertiesEXT -> Word64
drmFormatModifier :: Word64 }
deriving (Typeable, ImageDrmFormatModifierPropertiesEXT
-> ImageDrmFormatModifierPropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageDrmFormatModifierPropertiesEXT
-> ImageDrmFormatModifierPropertiesEXT -> Bool
$c/= :: ImageDrmFormatModifierPropertiesEXT
-> ImageDrmFormatModifierPropertiesEXT -> Bool
== :: ImageDrmFormatModifierPropertiesEXT
-> ImageDrmFormatModifierPropertiesEXT -> Bool
$c== :: ImageDrmFormatModifierPropertiesEXT
-> ImageDrmFormatModifierPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageDrmFormatModifierPropertiesEXT)
#endif
deriving instance Show ImageDrmFormatModifierPropertiesEXT
instance ToCStruct ImageDrmFormatModifierPropertiesEXT where
withCStruct :: forall b.
ImageDrmFormatModifierPropertiesEXT
-> (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO b)
-> IO b
withCStruct ImageDrmFormatModifierPropertiesEXT
x ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p ImageDrmFormatModifierPropertiesEXT
x (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT) -> IO b
f "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p)
pokeCStruct :: forall b.
("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> ImageDrmFormatModifierPropertiesEXT -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p ImageDrmFormatModifierPropertiesEXT{Word64
drmFormatModifier :: Word64
$sel:drmFormatModifier:ImageDrmFormatModifierPropertiesEXT :: ImageDrmFormatModifierPropertiesEXT -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
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 (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
drmFormatModifier)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO b -> IO b
pokeZeroCStruct "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
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 (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImageDrmFormatModifierPropertiesEXT where
peekCStruct :: ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO ImageDrmFormatModifierPropertiesEXT
peekCStruct "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p = do
Word64
drmFormatModifier <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> ImageDrmFormatModifierPropertiesEXT
ImageDrmFormatModifierPropertiesEXT
Word64
drmFormatModifier
instance Storable ImageDrmFormatModifierPropertiesEXT where
sizeOf :: ImageDrmFormatModifierPropertiesEXT -> Int
sizeOf ~ImageDrmFormatModifierPropertiesEXT
_ = Int
24
alignment :: ImageDrmFormatModifierPropertiesEXT -> Int
alignment ~ImageDrmFormatModifierPropertiesEXT
_ = Int
8
peek :: ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> IO ImageDrmFormatModifierPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT)
-> ImageDrmFormatModifierPropertiesEXT -> IO ()
poke "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
ptr ImageDrmFormatModifierPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr ImageDrmFormatModifierPropertiesEXT
ptr ImageDrmFormatModifierPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageDrmFormatModifierPropertiesEXT where
zero :: ImageDrmFormatModifierPropertiesEXT
zero = Word64 -> ImageDrmFormatModifierPropertiesEXT
ImageDrmFormatModifierPropertiesEXT
forall a. Zero a => a
zero
data DrmFormatModifierPropertiesList2EXT = DrmFormatModifierPropertiesList2EXT
{
DrmFormatModifierPropertiesList2EXT -> Word32
drmFormatModifierCount :: Word32
,
DrmFormatModifierPropertiesList2EXT
-> Ptr DrmFormatModifierProperties2EXT
drmFormatModifierProperties :: Ptr DrmFormatModifierProperties2EXT
}
deriving (Typeable, DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> Bool
$c/= :: DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> Bool
== :: DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> Bool
$c== :: DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrmFormatModifierPropertiesList2EXT)
#endif
deriving instance Show DrmFormatModifierPropertiesList2EXT
instance ToCStruct DrmFormatModifierPropertiesList2EXT where
withCStruct :: forall b.
DrmFormatModifierPropertiesList2EXT
-> (Ptr DrmFormatModifierPropertiesList2EXT -> IO b) -> IO b
withCStruct DrmFormatModifierPropertiesList2EXT
x Ptr DrmFormatModifierPropertiesList2EXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr DrmFormatModifierPropertiesList2EXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesList2EXT
p DrmFormatModifierPropertiesList2EXT
x (Ptr DrmFormatModifierPropertiesList2EXT -> IO b
f Ptr DrmFormatModifierPropertiesList2EXT
p)
pokeCStruct :: forall b.
Ptr DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesList2EXT
p DrmFormatModifierPropertiesList2EXT{Word32
Ptr DrmFormatModifierProperties2EXT
drmFormatModifierProperties :: Ptr DrmFormatModifierProperties2EXT
drmFormatModifierCount :: Word32
$sel:drmFormatModifierProperties:DrmFormatModifierPropertiesList2EXT :: DrmFormatModifierPropertiesList2EXT
-> Ptr DrmFormatModifierProperties2EXT
$sel:drmFormatModifierCount:DrmFormatModifierPropertiesList2EXT :: DrmFormatModifierPropertiesList2EXT -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_2_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesList2EXT
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 DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
drmFormatModifierCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DrmFormatModifierProperties2EXT))) (Ptr DrmFormatModifierProperties2EXT
drmFormatModifierProperties)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DrmFormatModifierPropertiesList2EXT -> IO b -> IO b
pokeZeroCStruct Ptr DrmFormatModifierPropertiesList2EXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_2_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct DrmFormatModifierPropertiesList2EXT where
peekCStruct :: Ptr DrmFormatModifierPropertiesList2EXT
-> IO DrmFormatModifierPropertiesList2EXT
peekCStruct Ptr DrmFormatModifierPropertiesList2EXT
p = do
Word32
drmFormatModifierCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr DrmFormatModifierProperties2EXT
pDrmFormatModifierProperties <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr DrmFormatModifierProperties2EXT) ((Ptr DrmFormatModifierPropertiesList2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr DrmFormatModifierProperties2EXT)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Ptr DrmFormatModifierProperties2EXT
-> DrmFormatModifierPropertiesList2EXT
DrmFormatModifierPropertiesList2EXT
Word32
drmFormatModifierCount Ptr DrmFormatModifierProperties2EXT
pDrmFormatModifierProperties
instance Storable DrmFormatModifierPropertiesList2EXT where
sizeOf :: DrmFormatModifierPropertiesList2EXT -> Int
sizeOf ~DrmFormatModifierPropertiesList2EXT
_ = Int
32
alignment :: DrmFormatModifierPropertiesList2EXT -> Int
alignment ~DrmFormatModifierPropertiesList2EXT
_ = Int
8
peek :: Ptr DrmFormatModifierPropertiesList2EXT
-> IO DrmFormatModifierPropertiesList2EXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrmFormatModifierPropertiesList2EXT
-> DrmFormatModifierPropertiesList2EXT -> IO ()
poke Ptr DrmFormatModifierPropertiesList2EXT
ptr DrmFormatModifierPropertiesList2EXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierPropertiesList2EXT
ptr DrmFormatModifierPropertiesList2EXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrmFormatModifierPropertiesList2EXT where
zero :: DrmFormatModifierPropertiesList2EXT
zero = Word32
-> Ptr DrmFormatModifierProperties2EXT
-> DrmFormatModifierPropertiesList2EXT
DrmFormatModifierPropertiesList2EXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data DrmFormatModifierProperties2EXT = DrmFormatModifierProperties2EXT
{
DrmFormatModifierProperties2EXT -> Word64
drmFormatModifier :: Word64
,
DrmFormatModifierProperties2EXT -> Word32
drmFormatModifierPlaneCount :: Word32
,
DrmFormatModifierProperties2EXT -> FormatFeatureFlags2
drmFormatModifierTilingFeatures :: FormatFeatureFlags2
}
deriving (Typeable, DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> Bool
$c/= :: DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> Bool
== :: DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> Bool
$c== :: DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrmFormatModifierProperties2EXT)
#endif
deriving instance Show DrmFormatModifierProperties2EXT
instance ToCStruct DrmFormatModifierProperties2EXT where
withCStruct :: forall b.
DrmFormatModifierProperties2EXT
-> (Ptr DrmFormatModifierProperties2EXT -> IO b) -> IO b
withCStruct DrmFormatModifierProperties2EXT
x Ptr DrmFormatModifierProperties2EXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DrmFormatModifierProperties2EXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierProperties2EXT
p DrmFormatModifierProperties2EXT
x (Ptr DrmFormatModifierProperties2EXT -> IO b
f Ptr DrmFormatModifierProperties2EXT
p)
pokeCStruct :: forall b.
Ptr DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierProperties2EXT
p DrmFormatModifierProperties2EXT{Word32
Word64
FormatFeatureFlags2
drmFormatModifierTilingFeatures :: FormatFeatureFlags2
drmFormatModifierPlaneCount :: Word32
drmFormatModifier :: Word64
$sel:drmFormatModifierTilingFeatures:DrmFormatModifierProperties2EXT :: DrmFormatModifierProperties2EXT -> FormatFeatureFlags2
$sel:drmFormatModifierPlaneCount:DrmFormatModifierProperties2EXT :: DrmFormatModifierProperties2EXT -> Word32
$sel:drmFormatModifier:DrmFormatModifierProperties2EXT :: DrmFormatModifierProperties2EXT -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64)) (Word64
drmFormatModifier)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Word32
drmFormatModifierPlaneCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr FormatFeatureFlags2)) (FormatFeatureFlags2
drmFormatModifierTilingFeatures)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DrmFormatModifierProperties2EXT -> IO b -> IO b
pokeZeroCStruct Ptr DrmFormatModifierProperties2EXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr FormatFeatureFlags2)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DrmFormatModifierProperties2EXT where
peekCStruct :: Ptr DrmFormatModifierProperties2EXT
-> IO DrmFormatModifierProperties2EXT
peekCStruct Ptr DrmFormatModifierProperties2EXT
p = do
Word64
drmFormatModifier <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word64))
Word32
drmFormatModifierPlaneCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
FormatFeatureFlags2
drmFormatModifierTilingFeatures <- forall a. Storable a => Ptr a -> IO a
peek @FormatFeatureFlags2 ((Ptr DrmFormatModifierProperties2EXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr FormatFeatureFlags2))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64
-> Word32 -> FormatFeatureFlags2 -> DrmFormatModifierProperties2EXT
DrmFormatModifierProperties2EXT
Word64
drmFormatModifier
Word32
drmFormatModifierPlaneCount
FormatFeatureFlags2
drmFormatModifierTilingFeatures
instance Storable DrmFormatModifierProperties2EXT where
sizeOf :: DrmFormatModifierProperties2EXT -> Int
sizeOf ~DrmFormatModifierProperties2EXT
_ = Int
24
alignment :: DrmFormatModifierProperties2EXT -> Int
alignment ~DrmFormatModifierProperties2EXT
_ = Int
8
peek :: Ptr DrmFormatModifierProperties2EXT
-> IO DrmFormatModifierProperties2EXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DrmFormatModifierProperties2EXT
-> DrmFormatModifierProperties2EXT -> IO ()
poke Ptr DrmFormatModifierProperties2EXT
ptr DrmFormatModifierProperties2EXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrmFormatModifierProperties2EXT
ptr DrmFormatModifierProperties2EXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrmFormatModifierProperties2EXT where
zero :: DrmFormatModifierProperties2EXT
zero = Word64
-> Word32 -> FormatFeatureFlags2 -> DrmFormatModifierProperties2EXT
DrmFormatModifierProperties2EXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type EXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION = 2
pattern EXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION :: forall a. Integral a => a
$mEXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_IMAGE_DRM_FORMAT_MODIFIER_SPEC_VERSION = 2
type EXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME = "VK_EXT_image_drm_format_modifier"
pattern EXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_IMAGE_DRM_FORMAT_MODIFIER_EXTENSION_NAME = "VK_EXT_image_drm_format_modifier"