{-# language CPP #-}
module Vulkan.Extensions.VK_QCOM_tile_properties ( getFramebufferTilePropertiesQCOM
, getDynamicRenderingTilePropertiesQCOM
, PhysicalDeviceTilePropertiesFeaturesQCOM(..)
, TilePropertiesQCOM(..)
, QCOM_TILE_PROPERTIES_SPEC_VERSION
, pattern QCOM_TILE_PROPERTIES_SPEC_VERSION
, QCOM_TILE_PROPERTIES_EXTENSION_NAME
, pattern QCOM_TILE_PROPERTIES_EXTENSION_NAME
, RenderingInfoKHR
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
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 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.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetDynamicRenderingTilePropertiesQCOM))
import Vulkan.Dynamic (DeviceCmds(pVkGetFramebufferTilePropertiesQCOM))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.Core10.FundamentalTypes (Extent2D)
import Vulkan.Core10.FundamentalTypes (Extent3D)
import Vulkan.Core10.Handles (Framebuffer)
import Vulkan.Core10.Handles (Framebuffer(..))
import Vulkan.Core10.FundamentalTypes (Offset2D)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering (RenderingInfo)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_TILE_PROPERTIES_FEATURES_QCOM))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_TILE_PROPERTIES_QCOM))
import Vulkan.Extensions.VK_KHR_dynamic_rendering (RenderingInfoKHR)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetFramebufferTilePropertiesQCOM
:: FunPtr (Ptr Device_T -> Framebuffer -> Ptr Word32 -> Ptr TilePropertiesQCOM -> IO Result) -> Ptr Device_T -> Framebuffer -> Ptr Word32 -> Ptr TilePropertiesQCOM -> IO Result
getFramebufferTilePropertiesQCOM :: forall io
. (MonadIO io)
=>
Device
->
Framebuffer
-> io (Result, ("properties" ::: Vector TilePropertiesQCOM))
getFramebufferTilePropertiesQCOM :: forall (io :: * -> *).
MonadIO io =>
Device
-> Framebuffer
-> io (Result, "properties" ::: Vector TilePropertiesQCOM)
getFramebufferTilePropertiesQCOM Device
device Framebuffer
framebuffer = 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 vkGetFramebufferTilePropertiesQCOMPtr :: FunPtr
(Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetFramebufferTilePropertiesQCOMPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
pVkGetFramebufferTilePropertiesQCOM (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
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetFramebufferTilePropertiesQCOMPtr 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 vkGetFramebufferTilePropertiesQCOM is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetFramebufferTilePropertiesQCOM' :: Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
vkGetFramebufferTilePropertiesQCOM' = FunPtr
(Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
-> Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
mkVkGetFramebufferTilePropertiesQCOM FunPtr
(Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetFramebufferTilePropertiesQCOMPtr
let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
"pPropertiesCount" ::: Ptr Word32
pPPropertiesCount <- 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 c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word32 Int
4) forall a. Ptr a -> IO ()
free
Result
_ <- 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
"vkGetFramebufferTilePropertiesQCOM" (Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
vkGetFramebufferTilePropertiesQCOM'
Ptr Device_T
device'
(Framebuffer
framebuffer)
("pPropertiesCount" ::: Ptr Word32
pPPropertiesCount)
(forall a. Ptr a
nullPtr))
Word32
pPropertiesCount <- 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 -> IO a
peek @Word32 "pPropertiesCount" ::: Ptr Word32
pPPropertiesCount
"pProperties" ::: Ptr TilePropertiesQCOM
pPProperties <- 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 c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @TilePropertiesQCOM ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertiesCount)) forall a. Num a => a -> a -> a
* Int
48)) forall a. Ptr a -> IO ()
free
[()]
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Int
i -> 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. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr TilePropertiesQCOM
pPProperties forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i forall a. Num a => a -> a -> a
* Int
48) :: Ptr TilePropertiesQCOM) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) [Int
0..(forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertiesCount)) forall a. Num a => a -> a -> a
- Int
1]
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
"vkGetFramebufferTilePropertiesQCOM" (Ptr Device_T
-> Framebuffer
-> ("pPropertiesCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
vkGetFramebufferTilePropertiesQCOM'
Ptr Device_T
device'
(Framebuffer
framebuffer)
("pPropertiesCount" ::: Ptr Word32
pPPropertiesCount)
(("pProperties" ::: Ptr TilePropertiesQCOM
pPProperties)))
Word32
pPropertiesCount' <- 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 -> IO a
peek @Word32 "pPropertiesCount" ::: Ptr Word32
pPPropertiesCount
"properties" ::: Vector TilePropertiesQCOM
pProperties' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertiesCount')) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @TilePropertiesQCOM ((("pProperties" ::: Ptr TilePropertiesQCOM
pPProperties) forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr TilePropertiesQCOM)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Result
r, "properties" ::: Vector TilePropertiesQCOM
pProperties')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDynamicRenderingTilePropertiesQCOM
:: FunPtr (Ptr Device_T -> Ptr (SomeStruct RenderingInfo) -> Ptr TilePropertiesQCOM -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct RenderingInfo) -> Ptr TilePropertiesQCOM -> IO Result
getDynamicRenderingTilePropertiesQCOM :: forall a io
. ( Extendss RenderingInfo a
, PokeChain a
, MonadIO io )
=>
Device
->
(RenderingInfo a)
-> io (TilePropertiesQCOM)
getDynamicRenderingTilePropertiesQCOM :: forall (a :: [*]) (io :: * -> *).
(Extendss RenderingInfo a, PokeChain a, MonadIO io) =>
Device -> RenderingInfo a -> io TilePropertiesQCOM
getDynamicRenderingTilePropertiesQCOM Device
device
RenderingInfo a
renderingInfo = 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 vkGetDynamicRenderingTilePropertiesQCOMPtr :: FunPtr
(Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetDynamicRenderingTilePropertiesQCOMPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
pVkGetDynamicRenderingTilePropertiesQCOM (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> 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
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetDynamicRenderingTilePropertiesQCOMPtr 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 vkGetDynamicRenderingTilePropertiesQCOM is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetDynamicRenderingTilePropertiesQCOM' :: Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
vkGetDynamicRenderingTilePropertiesQCOM' = FunPtr
(Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
-> Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
mkVkGetDynamicRenderingTilePropertiesQCOM FunPtr
(Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result)
vkGetDynamicRenderingTilePropertiesQCOMPtr
Ptr (RenderingInfo a)
pRenderingInfo <- 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. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderingInfo a
renderingInfo)
"pProperties" ::: Ptr TilePropertiesQCOM
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 @TilePropertiesQCOM)
Result
_ <- 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
"vkGetDynamicRenderingTilePropertiesQCOM" (Ptr Device_T
-> ("pRenderingInfo" ::: Ptr (SomeStruct RenderingInfo))
-> ("pProperties" ::: Ptr TilePropertiesQCOM)
-> IO Result
vkGetDynamicRenderingTilePropertiesQCOM'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (RenderingInfo a)
pRenderingInfo)
("pProperties" ::: Ptr TilePropertiesQCOM
pPProperties))
TilePropertiesQCOM
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 @TilePropertiesQCOM "pProperties" ::: Ptr TilePropertiesQCOM
pPProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (TilePropertiesQCOM
pProperties)
data PhysicalDeviceTilePropertiesFeaturesQCOM = PhysicalDeviceTilePropertiesFeaturesQCOM
{
PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
tileProperties :: Bool }
deriving (Typeable, PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
$c/= :: PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
== :: PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
$c== :: PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceTilePropertiesFeaturesQCOM)
#endif
deriving instance Show PhysicalDeviceTilePropertiesFeaturesQCOM
instance ToCStruct PhysicalDeviceTilePropertiesFeaturesQCOM where
withCStruct :: forall b.
PhysicalDeviceTilePropertiesFeaturesQCOM
-> (Ptr PhysicalDeviceTilePropertiesFeaturesQCOM -> IO b) -> IO b
withCStruct PhysicalDeviceTilePropertiesFeaturesQCOM
x Ptr PhysicalDeviceTilePropertiesFeaturesQCOM -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p PhysicalDeviceTilePropertiesFeaturesQCOM
x (Ptr PhysicalDeviceTilePropertiesFeaturesQCOM -> IO b
f Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p PhysicalDeviceTilePropertiesFeaturesQCOM{Bool
tileProperties :: Bool
$sel:tileProperties:PhysicalDeviceTilePropertiesFeaturesQCOM :: PhysicalDeviceTilePropertiesFeaturesQCOM -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TILE_PROPERTIES_FEATURES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
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 PhysicalDeviceTilePropertiesFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
tileProperties))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceTilePropertiesFeaturesQCOM -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TILE_PROPERTIES_FEATURES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
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 PhysicalDeviceTilePropertiesFeaturesQCOM
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 PhysicalDeviceTilePropertiesFeaturesQCOM where
peekCStruct :: Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
-> IO PhysicalDeviceTilePropertiesFeaturesQCOM
peekCStruct Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
p = do
Bool32
tileProperties <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
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 -> PhysicalDeviceTilePropertiesFeaturesQCOM
PhysicalDeviceTilePropertiesFeaturesQCOM
(Bool32 -> Bool
bool32ToBool Bool32
tileProperties)
instance Storable PhysicalDeviceTilePropertiesFeaturesQCOM where
sizeOf :: PhysicalDeviceTilePropertiesFeaturesQCOM -> Int
sizeOf ~PhysicalDeviceTilePropertiesFeaturesQCOM
_ = Int
24
alignment :: PhysicalDeviceTilePropertiesFeaturesQCOM -> Int
alignment ~PhysicalDeviceTilePropertiesFeaturesQCOM
_ = Int
8
peek :: Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
-> IO PhysicalDeviceTilePropertiesFeaturesQCOM
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
-> PhysicalDeviceTilePropertiesFeaturesQCOM -> IO ()
poke Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
ptr PhysicalDeviceTilePropertiesFeaturesQCOM
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTilePropertiesFeaturesQCOM
ptr PhysicalDeviceTilePropertiesFeaturesQCOM
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceTilePropertiesFeaturesQCOM where
zero :: PhysicalDeviceTilePropertiesFeaturesQCOM
zero = Bool -> PhysicalDeviceTilePropertiesFeaturesQCOM
PhysicalDeviceTilePropertiesFeaturesQCOM
forall a. Zero a => a
zero
data TilePropertiesQCOM = TilePropertiesQCOM
{
TilePropertiesQCOM -> Extent3D
tileSize :: Extent3D
,
TilePropertiesQCOM -> Extent2D
apronSize :: Extent2D
,
TilePropertiesQCOM -> Offset2D
origin :: Offset2D
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (TilePropertiesQCOM)
#endif
deriving instance Show TilePropertiesQCOM
instance ToCStruct TilePropertiesQCOM where
withCStruct :: forall b.
TilePropertiesQCOM
-> (("pProperties" ::: Ptr TilePropertiesQCOM) -> IO b) -> IO b
withCStruct TilePropertiesQCOM
x ("pProperties" ::: Ptr TilePropertiesQCOM) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \"pProperties" ::: Ptr TilePropertiesQCOM
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr TilePropertiesQCOM
p TilePropertiesQCOM
x (("pProperties" ::: Ptr TilePropertiesQCOM) -> IO b
f "pProperties" ::: Ptr TilePropertiesQCOM
p)
pokeCStruct :: forall b.
("pProperties" ::: Ptr TilePropertiesQCOM)
-> TilePropertiesQCOM -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr TilePropertiesQCOM
p TilePropertiesQCOM{Offset2D
Extent3D
Extent2D
origin :: Offset2D
apronSize :: Extent2D
tileSize :: Extent3D
$sel:origin:TilePropertiesQCOM :: TilePropertiesQCOM -> Offset2D
$sel:apronSize:TilePropertiesQCOM :: TilePropertiesQCOM -> Extent2D
$sel:tileSize:TilePropertiesQCOM :: TilePropertiesQCOM -> Extent3D
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_TILE_PROPERTIES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
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 TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent3D)) (Extent3D
tileSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Extent2D)) (Extent2D
apronSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Offset2D)) (Offset2D
origin)
IO b
f
cStructSize :: Int
cStructSize = Int
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pProperties" ::: Ptr TilePropertiesQCOM) -> IO b -> IO b
pokeZeroCStruct "pProperties" ::: Ptr TilePropertiesQCOM
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_TILE_PROPERTIES_QCOM)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
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 TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent3D)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Offset2D)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct TilePropertiesQCOM where
peekCStruct :: ("pProperties" ::: Ptr TilePropertiesQCOM) -> IO TilePropertiesQCOM
peekCStruct "pProperties" ::: Ptr TilePropertiesQCOM
p = do
Extent3D
tileSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent3D (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent3D))
Extent2D
apronSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Extent2D))
Offset2D
origin <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Offset2D (("pProperties" ::: Ptr TilePropertiesQCOM
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Offset2D))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Extent3D -> Extent2D -> Offset2D -> TilePropertiesQCOM
TilePropertiesQCOM
Extent3D
tileSize Extent2D
apronSize Offset2D
origin
instance Storable TilePropertiesQCOM where
sizeOf :: TilePropertiesQCOM -> Int
sizeOf ~TilePropertiesQCOM
_ = Int
48
alignment :: TilePropertiesQCOM -> Int
alignment ~TilePropertiesQCOM
_ = Int
8
peek :: ("pProperties" ::: Ptr TilePropertiesQCOM) -> IO TilePropertiesQCOM
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pProperties" ::: Ptr TilePropertiesQCOM)
-> TilePropertiesQCOM -> IO ()
poke "pProperties" ::: Ptr TilePropertiesQCOM
ptr TilePropertiesQCOM
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr TilePropertiesQCOM
ptr TilePropertiesQCOM
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero TilePropertiesQCOM where
zero :: TilePropertiesQCOM
zero = Extent3D -> Extent2D -> Offset2D -> TilePropertiesQCOM
TilePropertiesQCOM
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type QCOM_TILE_PROPERTIES_SPEC_VERSION = 1
pattern QCOM_TILE_PROPERTIES_SPEC_VERSION :: forall a . Integral a => a
pattern $bQCOM_TILE_PROPERTIES_SPEC_VERSION :: forall a. Integral a => a
$mQCOM_TILE_PROPERTIES_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_TILE_PROPERTIES_SPEC_VERSION = 1
type QCOM_TILE_PROPERTIES_EXTENSION_NAME = "VK_QCOM_tile_properties"
pattern QCOM_TILE_PROPERTIES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bQCOM_TILE_PROPERTIES_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mQCOM_TILE_PROPERTIES_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
QCOM_TILE_PROPERTIES_EXTENSION_NAME = "VK_QCOM_tile_properties"