{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_sample_locations ( cmdSetSampleLocationsEXT
, getPhysicalDeviceMultisamplePropertiesEXT
, SampleLocationEXT(..)
, SampleLocationsInfoEXT(..)
, AttachmentSampleLocationsEXT(..)
, SubpassSampleLocationsEXT(..)
, RenderPassSampleLocationsBeginInfoEXT(..)
, PipelineSampleLocationsStateCreateInfoEXT(..)
, PhysicalDeviceSampleLocationsPropertiesEXT(..)
, MultisamplePropertiesEXT(..)
, EXT_SAMPLE_LOCATIONS_SPEC_VERSION
, pattern EXT_SAMPLE_LOCATIONS_SPEC_VERSION
, EXT_SAMPLE_LOCATIONS_EXTENSION_NAME
, pattern EXT_SAMPLE_LOCATIONS_EXTENSION_NAME
) where
import Vulkan.CStruct.Utils (FixedArray)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
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.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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.Utils (lowerArrayPtr)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetSampleLocationsEXT))
import Vulkan.Core10.FundamentalTypes (Extent2D)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceMultisamplePropertiesEXT))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(PhysicalDevice))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MULTISAMPLE_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLE_LOCATIONS_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_SAMPLE_LOCATIONS_STATE_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_SAMPLE_LOCATIONS_BEGIN_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SAMPLE_LOCATIONS_INFO_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdSetSampleLocationsEXT
:: FunPtr (Ptr CommandBuffer_T -> Ptr SampleLocationsInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr SampleLocationsInfoEXT -> IO ()
cmdSetSampleLocationsEXT :: forall io
. (MonadIO io)
=>
CommandBuffer
->
SampleLocationsInfoEXT
-> io ()
cmdSetSampleLocationsEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> SampleLocationsInfoEXT -> io ()
cmdSetSampleLocationsEXT CommandBuffer
commandBuffer
SampleLocationsInfoEXT
sampleLocationsInfo = 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 vkCmdSetSampleLocationsEXTPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ())
vkCmdSetSampleLocationsEXTPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ())
pVkCmdSetSampleLocationsEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ())
vkCmdSetSampleLocationsEXTPtr 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 vkCmdSetSampleLocationsEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCmdSetSampleLocationsEXT' :: Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT) -> IO ()
vkCmdSetSampleLocationsEXT' = FunPtr
(Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ())
-> Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ()
mkVkCmdSetSampleLocationsEXT FunPtr
(Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO ())
vkCmdSetSampleLocationsEXTPtr
"pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
pSampleLocationsInfo <- 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 (SampleLocationsInfoEXT
sampleLocationsInfo)
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
"vkCmdSetSampleLocationsEXT" (Ptr CommandBuffer_T
-> ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT) -> IO ()
vkCmdSetSampleLocationsEXT'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
"pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
pSampleLocationsInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPhysicalDeviceMultisamplePropertiesEXT
:: FunPtr (Ptr PhysicalDevice_T -> SampleCountFlagBits -> Ptr MultisamplePropertiesEXT -> IO ()) -> Ptr PhysicalDevice_T -> SampleCountFlagBits -> Ptr MultisamplePropertiesEXT -> IO ()
getPhysicalDeviceMultisamplePropertiesEXT :: forall io
. (MonadIO io)
=>
PhysicalDevice
->
("samples" ::: SampleCountFlagBits)
-> io (MultisamplePropertiesEXT)
getPhysicalDeviceMultisamplePropertiesEXT :: forall (io :: * -> *).
MonadIO io =>
PhysicalDevice
-> ("samples" ::: SampleCountFlagBits)
-> io MultisamplePropertiesEXT
getPhysicalDeviceMultisamplePropertiesEXT PhysicalDevice
physicalDevice
"samples" ::: SampleCountFlagBits
samples = 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 vkGetPhysicalDeviceMultisamplePropertiesEXTPtr :: FunPtr
(Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ())
vkGetPhysicalDeviceMultisamplePropertiesEXTPtr = InstanceCmds
-> FunPtr
(Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ())
pVkGetPhysicalDeviceMultisamplePropertiesEXT (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
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 PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ())
vkGetPhysicalDeviceMultisamplePropertiesEXTPtr 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 vkGetPhysicalDeviceMultisamplePropertiesEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetPhysicalDeviceMultisamplePropertiesEXT' :: Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ()
vkGetPhysicalDeviceMultisamplePropertiesEXT' = FunPtr
(Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ())
-> Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ()
mkVkGetPhysicalDeviceMultisamplePropertiesEXT FunPtr
(Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ())
vkGetPhysicalDeviceMultisamplePropertiesEXTPtr
"pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
pPMultisampleProperties <- 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 @MultisamplePropertiesEXT)
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
"vkGetPhysicalDeviceMultisamplePropertiesEXT" (Ptr PhysicalDevice_T
-> ("samples" ::: SampleCountFlagBits)
-> ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO ()
vkGetPhysicalDeviceMultisamplePropertiesEXT'
(PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice))
("samples" ::: SampleCountFlagBits
samples)
("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
pPMultisampleProperties))
MultisamplePropertiesEXT
pMultisampleProperties <- 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 @MultisamplePropertiesEXT "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
pPMultisampleProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (MultisamplePropertiesEXT
pMultisampleProperties)
data SampleLocationEXT = SampleLocationEXT
{
SampleLocationEXT -> Float
x :: Float
,
SampleLocationEXT -> Float
y :: Float
}
deriving (Typeable, SampleLocationEXT -> SampleLocationEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SampleLocationEXT -> SampleLocationEXT -> Bool
$c/= :: SampleLocationEXT -> SampleLocationEXT -> Bool
== :: SampleLocationEXT -> SampleLocationEXT -> Bool
$c== :: SampleLocationEXT -> SampleLocationEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SampleLocationEXT)
#endif
deriving instance Show SampleLocationEXT
instance ToCStruct SampleLocationEXT where
withCStruct :: forall b.
SampleLocationEXT -> (Ptr SampleLocationEXT -> IO b) -> IO b
withCStruct SampleLocationEXT
x Ptr SampleLocationEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 forall a b. (a -> b) -> a -> b
$ \Ptr SampleLocationEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SampleLocationEXT
p SampleLocationEXT
x (Ptr SampleLocationEXT -> IO b
f Ptr SampleLocationEXT
p)
pokeCStruct :: forall b.
Ptr SampleLocationEXT -> SampleLocationEXT -> IO b -> IO b
pokeCStruct Ptr SampleLocationEXT
p SampleLocationEXT{Float
y :: Float
x :: Float
$sel:y:SampleLocationEXT :: SampleLocationEXT -> Float
$sel:x:SampleLocationEXT :: SampleLocationEXT -> Float
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
x))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
y))
IO b
f
cStructSize :: Int
cStructSize = Int
8
cStructAlignment :: Int
cStructAlignment = Int
4
pokeZeroCStruct :: forall b. Ptr SampleLocationEXT -> IO b -> IO b
pokeZeroCStruct Ptr SampleLocationEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct SampleLocationEXT where
peekCStruct :: Ptr SampleLocationEXT -> IO SampleLocationEXT
peekCStruct Ptr SampleLocationEXT
p = do
CFloat
x <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat))
CFloat
y <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr SampleLocationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Float -> Float -> SampleLocationEXT
SampleLocationEXT
(coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
x) (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
y)
instance Storable SampleLocationEXT where
sizeOf :: SampleLocationEXT -> Int
sizeOf ~SampleLocationEXT
_ = Int
8
alignment :: SampleLocationEXT -> Int
alignment ~SampleLocationEXT
_ = Int
4
peek :: Ptr SampleLocationEXT -> IO SampleLocationEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SampleLocationEXT -> SampleLocationEXT -> IO ()
poke Ptr SampleLocationEXT
ptr SampleLocationEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SampleLocationEXT
ptr SampleLocationEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SampleLocationEXT where
zero :: SampleLocationEXT
zero = Float -> Float -> SampleLocationEXT
SampleLocationEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data SampleLocationsInfoEXT = SampleLocationsInfoEXT
{
SampleLocationsInfoEXT -> "samples" ::: SampleCountFlagBits
sampleLocationsPerPixel :: SampleCountFlagBits
,
SampleLocationsInfoEXT -> Extent2D
sampleLocationGridSize :: Extent2D
,
SampleLocationsInfoEXT -> Vector SampleLocationEXT
sampleLocations :: Vector SampleLocationEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SampleLocationsInfoEXT)
#endif
deriving instance Show SampleLocationsInfoEXT
instance ToCStruct SampleLocationsInfoEXT where
withCStruct :: forall b.
SampleLocationsInfoEXT
-> (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO b)
-> IO b
withCStruct SampleLocationsInfoEXT
x ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p SampleLocationsInfoEXT
x (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT) -> IO b
f "pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p)
pokeCStruct :: forall b.
("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> SampleLocationsInfoEXT -> IO b -> IO b
pokeCStruct "pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p SampleLocationsInfoEXT{Vector SampleLocationEXT
"samples" ::: SampleCountFlagBits
Extent2D
sampleLocations :: Vector SampleLocationEXT
sampleLocationGridSize :: Extent2D
sampleLocationsPerPixel :: "samples" ::: SampleCountFlagBits
$sel:sampleLocations:SampleLocationsInfoEXT :: SampleLocationsInfoEXT -> Vector SampleLocationEXT
$sel:sampleLocationGridSize:SampleLocationsInfoEXT :: SampleLocationsInfoEXT -> Extent2D
$sel:sampleLocationsPerPixel:SampleLocationsInfoEXT :: SampleLocationsInfoEXT -> "samples" ::: SampleCountFlagBits
..} 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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLE_LOCATIONS_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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlagBits)) ("samples" ::: SampleCountFlagBits
sampleLocationsPerPixel)
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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D)) (Extent2D
sampleLocationGridSize)
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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
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 SampleLocationEXT
sampleLocations)) :: Word32))
Ptr SampleLocationEXT
pPSampleLocations' <- 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 @SampleLocationEXT ((forall a. Vector a -> Int
Data.Vector.length (Vector SampleLocationEXT
sampleLocations)) 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 SampleLocationEXT
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SampleLocationEXT
pPSampleLocations' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SampleLocationEXT) (SampleLocationEXT
e)) (Vector SampleLocationEXT
sampleLocations)
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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr SampleLocationEXT))) (Ptr SampleLocationEXT
pPSampleLocations')
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.
("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SAMPLE_LOCATIONS_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
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 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlagBits)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SampleLocationsInfoEXT where
peekCStruct :: ("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT)
-> IO SampleLocationsInfoEXT
peekCStruct "pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p = do
"samples" ::: SampleCountFlagBits
sampleLocationsPerPixel <- forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlagBits))
Extent2D
sampleLocationGridSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D))
Word32
sampleLocationsCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
Ptr SampleLocationEXT
pSampleLocations <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr SampleLocationEXT) (("pSampleLocationsInfo" ::: Ptr SampleLocationsInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr SampleLocationEXT)))
Vector SampleLocationEXT
pSampleLocations' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
sampleLocationsCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SampleLocationEXT ((Ptr SampleLocationEXT
pSampleLocations forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SampleLocationEXT)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("samples" ::: SampleCountFlagBits)
-> Extent2D -> Vector SampleLocationEXT -> SampleLocationsInfoEXT
SampleLocationsInfoEXT
"samples" ::: SampleCountFlagBits
sampleLocationsPerPixel Extent2D
sampleLocationGridSize Vector SampleLocationEXT
pSampleLocations'
instance Zero SampleLocationsInfoEXT where
zero :: SampleLocationsInfoEXT
zero = ("samples" ::: SampleCountFlagBits)
-> Extent2D -> Vector SampleLocationEXT -> SampleLocationsInfoEXT
SampleLocationsInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Monoid a => a
mempty
data AttachmentSampleLocationsEXT = AttachmentSampleLocationsEXT
{
AttachmentSampleLocationsEXT -> Word32
attachmentIndex :: Word32
,
AttachmentSampleLocationsEXT -> SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AttachmentSampleLocationsEXT)
#endif
deriving instance Show AttachmentSampleLocationsEXT
instance ToCStruct AttachmentSampleLocationsEXT where
withCStruct :: forall b.
AttachmentSampleLocationsEXT
-> (Ptr AttachmentSampleLocationsEXT -> IO b) -> IO b
withCStruct AttachmentSampleLocationsEXT
x Ptr AttachmentSampleLocationsEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr AttachmentSampleLocationsEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AttachmentSampleLocationsEXT
p AttachmentSampleLocationsEXT
x (Ptr AttachmentSampleLocationsEXT -> IO b
f Ptr AttachmentSampleLocationsEXT
p)
pokeCStruct :: forall b.
Ptr AttachmentSampleLocationsEXT
-> AttachmentSampleLocationsEXT -> IO b -> IO b
pokeCStruct Ptr AttachmentSampleLocationsEXT
p AttachmentSampleLocationsEXT{Word32
SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
attachmentIndex :: Word32
$sel:sampleLocationsInfo:AttachmentSampleLocationsEXT :: AttachmentSampleLocationsEXT -> SampleLocationsInfoEXT
$sel:attachmentIndex:AttachmentSampleLocationsEXT :: AttachmentSampleLocationsEXT -> Word32
..} 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 AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
attachmentIndex)
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT)) (SampleLocationsInfoEXT
sampleLocationsInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
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
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr AttachmentSampleLocationsEXT -> IO b -> IO b
pokeZeroCStruct Ptr AttachmentSampleLocationsEXT
p 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 AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (forall a. Zero a => a
zero)
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT)) (forall a. Zero a => a
zero) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct AttachmentSampleLocationsEXT where
peekCStruct :: Ptr AttachmentSampleLocationsEXT -> IO AttachmentSampleLocationsEXT
peekCStruct Ptr AttachmentSampleLocationsEXT
p = do
Word32
attachmentIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
SampleLocationsInfoEXT
sampleLocationsInfo <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SampleLocationsInfoEXT ((Ptr AttachmentSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> SampleLocationsInfoEXT -> AttachmentSampleLocationsEXT
AttachmentSampleLocationsEXT
Word32
attachmentIndex SampleLocationsInfoEXT
sampleLocationsInfo
instance Zero AttachmentSampleLocationsEXT where
zero :: AttachmentSampleLocationsEXT
zero = Word32 -> SampleLocationsInfoEXT -> AttachmentSampleLocationsEXT
AttachmentSampleLocationsEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data SubpassSampleLocationsEXT = SubpassSampleLocationsEXT
{
SubpassSampleLocationsEXT -> Word32
subpassIndex :: Word32
,
SubpassSampleLocationsEXT -> SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassSampleLocationsEXT)
#endif
deriving instance Show SubpassSampleLocationsEXT
instance ToCStruct SubpassSampleLocationsEXT where
withCStruct :: forall b.
SubpassSampleLocationsEXT
-> (Ptr SubpassSampleLocationsEXT -> IO b) -> IO b
withCStruct SubpassSampleLocationsEXT
x Ptr SubpassSampleLocationsEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr SubpassSampleLocationsEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassSampleLocationsEXT
p SubpassSampleLocationsEXT
x (Ptr SubpassSampleLocationsEXT -> IO b
f Ptr SubpassSampleLocationsEXT
p)
pokeCStruct :: forall b.
Ptr SubpassSampleLocationsEXT
-> SubpassSampleLocationsEXT -> IO b -> IO b
pokeCStruct Ptr SubpassSampleLocationsEXT
p SubpassSampleLocationsEXT{Word32
SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
subpassIndex :: Word32
$sel:sampleLocationsInfo:SubpassSampleLocationsEXT :: SubpassSampleLocationsEXT -> SampleLocationsInfoEXT
$sel:subpassIndex:SubpassSampleLocationsEXT :: SubpassSampleLocationsEXT -> Word32
..} 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 SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Word32
subpassIndex)
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT)) (SampleLocationsInfoEXT
sampleLocationsInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
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
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr SubpassSampleLocationsEXT -> IO b -> IO b
pokeZeroCStruct Ptr SubpassSampleLocationsEXT
p 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 SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (forall a. Zero a => a
zero)
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT)) (forall a. Zero a => a
zero) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SubpassSampleLocationsEXT where
peekCStruct :: Ptr SubpassSampleLocationsEXT -> IO SubpassSampleLocationsEXT
peekCStruct Ptr SubpassSampleLocationsEXT
p = do
Word32
subpassIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
SampleLocationsInfoEXT
sampleLocationsInfo <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SampleLocationsInfoEXT ((Ptr SubpassSampleLocationsEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr SampleLocationsInfoEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> SampleLocationsInfoEXT -> SubpassSampleLocationsEXT
SubpassSampleLocationsEXT
Word32
subpassIndex SampleLocationsInfoEXT
sampleLocationsInfo
instance Zero SubpassSampleLocationsEXT where
zero :: SubpassSampleLocationsEXT
zero = Word32 -> SampleLocationsInfoEXT -> SubpassSampleLocationsEXT
SubpassSampleLocationsEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data RenderPassSampleLocationsBeginInfoEXT = RenderPassSampleLocationsBeginInfoEXT
{
RenderPassSampleLocationsBeginInfoEXT
-> Vector AttachmentSampleLocationsEXT
attachmentInitialSampleLocations :: Vector AttachmentSampleLocationsEXT
,
RenderPassSampleLocationsBeginInfoEXT
-> Vector SubpassSampleLocationsEXT
postSubpassSampleLocations :: Vector SubpassSampleLocationsEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassSampleLocationsBeginInfoEXT)
#endif
deriving instance Show RenderPassSampleLocationsBeginInfoEXT
instance ToCStruct RenderPassSampleLocationsBeginInfoEXT where
withCStruct :: forall b.
RenderPassSampleLocationsBeginInfoEXT
-> (Ptr RenderPassSampleLocationsBeginInfoEXT -> IO b) -> IO b
withCStruct RenderPassSampleLocationsBeginInfoEXT
x Ptr RenderPassSampleLocationsBeginInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr RenderPassSampleLocationsBeginInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RenderPassSampleLocationsBeginInfoEXT
p RenderPassSampleLocationsBeginInfoEXT
x (Ptr RenderPassSampleLocationsBeginInfoEXT -> IO b
f Ptr RenderPassSampleLocationsBeginInfoEXT
p)
pokeCStruct :: forall b.
Ptr RenderPassSampleLocationsBeginInfoEXT
-> RenderPassSampleLocationsBeginInfoEXT -> IO b -> IO b
pokeCStruct Ptr RenderPassSampleLocationsBeginInfoEXT
p RenderPassSampleLocationsBeginInfoEXT{Vector SubpassSampleLocationsEXT
Vector AttachmentSampleLocationsEXT
postSubpassSampleLocations :: Vector SubpassSampleLocationsEXT
attachmentInitialSampleLocations :: Vector AttachmentSampleLocationsEXT
$sel:postSubpassSampleLocations:RenderPassSampleLocationsBeginInfoEXT :: RenderPassSampleLocationsBeginInfoEXT
-> Vector SubpassSampleLocationsEXT
$sel:attachmentInitialSampleLocations:RenderPassSampleLocationsBeginInfoEXT :: RenderPassSampleLocationsBeginInfoEXT
-> Vector AttachmentSampleLocationsEXT
..} 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 RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_SAMPLE_LOCATIONS_BEGIN_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 RenderPassSampleLocationsBeginInfoEXT
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 RenderPassSampleLocationsBeginInfoEXT
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 AttachmentSampleLocationsEXT
attachmentInitialSampleLocations)) :: Word32))
Ptr AttachmentSampleLocationsEXT
pPAttachmentInitialSampleLocations' <- 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 @AttachmentSampleLocationsEXT ((forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentSampleLocationsEXT
attachmentInitialSampleLocations)) forall a. Num a => a -> a -> a
* Int
48)
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i AttachmentSampleLocationsEXT
e -> 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 -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentSampleLocationsEXT
pPAttachmentInitialSampleLocations' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentSampleLocationsEXT) (AttachmentSampleLocationsEXT
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentSampleLocationsEXT
attachmentInitialSampleLocations)
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 RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr AttachmentSampleLocationsEXT))) (Ptr AttachmentSampleLocationsEXT
pPAttachmentInitialSampleLocations')
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 RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: 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 SubpassSampleLocationsEXT
postSubpassSampleLocations)) :: Word32))
Ptr SubpassSampleLocationsEXT
pPPostSubpassSampleLocations' <- 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 @SubpassSampleLocationsEXT ((forall a. Vector a -> Int
Data.Vector.length (Vector SubpassSampleLocationsEXT
postSubpassSampleLocations)) forall a. Num a => a -> a -> a
* Int
48)
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i SubpassSampleLocationsEXT
e -> 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 -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassSampleLocationsEXT
pPPostSubpassSampleLocations' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassSampleLocationsEXT) (SubpassSampleLocationsEXT
e) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) (Vector SubpassSampleLocationsEXT
postSubpassSampleLocations)
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 RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr SubpassSampleLocationsEXT))) (Ptr SubpassSampleLocationsEXT
pPPostSubpassSampleLocations')
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
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr RenderPassSampleLocationsBeginInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr RenderPassSampleLocationsBeginInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_SAMPLE_LOCATIONS_BEGIN_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct RenderPassSampleLocationsBeginInfoEXT where
peekCStruct :: Ptr RenderPassSampleLocationsBeginInfoEXT
-> IO RenderPassSampleLocationsBeginInfoEXT
peekCStruct Ptr RenderPassSampleLocationsBeginInfoEXT
p = do
Word32
attachmentInitialSampleLocationsCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr AttachmentSampleLocationsEXT
pAttachmentInitialSampleLocations <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentSampleLocationsEXT) ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr AttachmentSampleLocationsEXT)))
Vector AttachmentSampleLocationsEXT
pAttachmentInitialSampleLocations' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
attachmentInitialSampleLocationsCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentSampleLocationsEXT ((Ptr AttachmentSampleLocationsEXT
pAttachmentInitialSampleLocations forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentSampleLocationsEXT)))
Word32
postSubpassSampleLocationsCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
Ptr SubpassSampleLocationsEXT
pPostSubpassSampleLocations <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubpassSampleLocationsEXT) ((Ptr RenderPassSampleLocationsBeginInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr (Ptr SubpassSampleLocationsEXT)))
Vector SubpassSampleLocationsEXT
pPostSubpassSampleLocations' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
postSubpassSampleLocationsCount) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubpassSampleLocationsEXT ((Ptr SubpassSampleLocationsEXT
pPostSubpassSampleLocations forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
48 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassSampleLocationsEXT)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector AttachmentSampleLocationsEXT
-> Vector SubpassSampleLocationsEXT
-> RenderPassSampleLocationsBeginInfoEXT
RenderPassSampleLocationsBeginInfoEXT
Vector AttachmentSampleLocationsEXT
pAttachmentInitialSampleLocations' Vector SubpassSampleLocationsEXT
pPostSubpassSampleLocations'
instance Zero RenderPassSampleLocationsBeginInfoEXT where
zero :: RenderPassSampleLocationsBeginInfoEXT
zero = Vector AttachmentSampleLocationsEXT
-> Vector SubpassSampleLocationsEXT
-> RenderPassSampleLocationsBeginInfoEXT
RenderPassSampleLocationsBeginInfoEXT
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
data PipelineSampleLocationsStateCreateInfoEXT = PipelineSampleLocationsStateCreateInfoEXT
{
PipelineSampleLocationsStateCreateInfoEXT -> Bool
sampleLocationsEnable :: Bool
,
PipelineSampleLocationsStateCreateInfoEXT -> SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineSampleLocationsStateCreateInfoEXT)
#endif
deriving instance Show PipelineSampleLocationsStateCreateInfoEXT
instance ToCStruct PipelineSampleLocationsStateCreateInfoEXT where
withCStruct :: forall b.
PipelineSampleLocationsStateCreateInfoEXT
-> (Ptr PipelineSampleLocationsStateCreateInfoEXT -> IO b) -> IO b
withCStruct PipelineSampleLocationsStateCreateInfoEXT
x Ptr PipelineSampleLocationsStateCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 forall a b. (a -> b) -> a -> b
$ \Ptr PipelineSampleLocationsStateCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineSampleLocationsStateCreateInfoEXT
p PipelineSampleLocationsStateCreateInfoEXT
x (Ptr PipelineSampleLocationsStateCreateInfoEXT -> IO b
f Ptr PipelineSampleLocationsStateCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr PipelineSampleLocationsStateCreateInfoEXT
-> PipelineSampleLocationsStateCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineSampleLocationsStateCreateInfoEXT
p PipelineSampleLocationsStateCreateInfoEXT{Bool
SampleLocationsInfoEXT
sampleLocationsInfo :: SampleLocationsInfoEXT
sampleLocationsEnable :: Bool
$sel:sampleLocationsInfo:PipelineSampleLocationsStateCreateInfoEXT :: PipelineSampleLocationsStateCreateInfoEXT -> SampleLocationsInfoEXT
$sel:sampleLocationsEnable:PipelineSampleLocationsStateCreateInfoEXT :: PipelineSampleLocationsStateCreateInfoEXT -> Bool
..} 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 PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SAMPLE_LOCATIONS_STATE_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 PipelineSampleLocationsStateCreateInfoEXT
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 PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sampleLocationsEnable))
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SampleLocationsInfoEXT)) (SampleLocationsInfoEXT
sampleLocationsInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
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
64
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PipelineSampleLocationsStateCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineSampleLocationsStateCreateInfoEXT
p 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 PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SAMPLE_LOCATIONS_STATE_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 PipelineSampleLocationsStateCreateInfoEXT
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 PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
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 -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SampleLocationsInfoEXT)) (forall a. Zero a => a
zero) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct PipelineSampleLocationsStateCreateInfoEXT where
peekCStruct :: Ptr PipelineSampleLocationsStateCreateInfoEXT
-> IO PipelineSampleLocationsStateCreateInfoEXT
peekCStruct Ptr PipelineSampleLocationsStateCreateInfoEXT
p = do
Bool32
sampleLocationsEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
SampleLocationsInfoEXT
sampleLocationsInfo <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SampleLocationsInfoEXT ((Ptr PipelineSampleLocationsStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SampleLocationsInfoEXT))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> SampleLocationsInfoEXT
-> PipelineSampleLocationsStateCreateInfoEXT
PipelineSampleLocationsStateCreateInfoEXT
(Bool32 -> Bool
bool32ToBool Bool32
sampleLocationsEnable) SampleLocationsInfoEXT
sampleLocationsInfo
instance Zero PipelineSampleLocationsStateCreateInfoEXT where
zero :: PipelineSampleLocationsStateCreateInfoEXT
zero = Bool
-> SampleLocationsInfoEXT
-> PipelineSampleLocationsStateCreateInfoEXT
PipelineSampleLocationsStateCreateInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceSampleLocationsPropertiesEXT = PhysicalDeviceSampleLocationsPropertiesEXT
{
PhysicalDeviceSampleLocationsPropertiesEXT
-> "samples" ::: SampleCountFlagBits
sampleLocationSampleCounts :: SampleCountFlags
,
PhysicalDeviceSampleLocationsPropertiesEXT -> Extent2D
maxSampleLocationGridSize :: Extent2D
,
PhysicalDeviceSampleLocationsPropertiesEXT -> (Float, Float)
sampleLocationCoordinateRange :: (Float, Float)
,
PhysicalDeviceSampleLocationsPropertiesEXT -> Word32
sampleLocationSubPixelBits :: Word32
,
PhysicalDeviceSampleLocationsPropertiesEXT -> Bool
variableSampleLocations :: Bool
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSampleLocationsPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceSampleLocationsPropertiesEXT
instance ToCStruct PhysicalDeviceSampleLocationsPropertiesEXT where
withCStruct :: forall b.
PhysicalDeviceSampleLocationsPropertiesEXT
-> (Ptr PhysicalDeviceSampleLocationsPropertiesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceSampleLocationsPropertiesEXT
x Ptr PhysicalDeviceSampleLocationsPropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p PhysicalDeviceSampleLocationsPropertiesEXT
x (Ptr PhysicalDeviceSampleLocationsPropertiesEXT -> IO b
f Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceSampleLocationsPropertiesEXT
-> PhysicalDeviceSampleLocationsPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p PhysicalDeviceSampleLocationsPropertiesEXT{Bool
Word32
(Float, Float)
"samples" ::: SampleCountFlagBits
Extent2D
variableSampleLocations :: Bool
sampleLocationSubPixelBits :: Word32
sampleLocationCoordinateRange :: (Float, Float)
maxSampleLocationGridSize :: Extent2D
sampleLocationSampleCounts :: "samples" ::: SampleCountFlagBits
$sel:variableSampleLocations:PhysicalDeviceSampleLocationsPropertiesEXT :: PhysicalDeviceSampleLocationsPropertiesEXT -> Bool
$sel:sampleLocationSubPixelBits:PhysicalDeviceSampleLocationsPropertiesEXT :: PhysicalDeviceSampleLocationsPropertiesEXT -> Word32
$sel:sampleLocationCoordinateRange:PhysicalDeviceSampleLocationsPropertiesEXT :: PhysicalDeviceSampleLocationsPropertiesEXT -> (Float, Float)
$sel:maxSampleLocationGridSize:PhysicalDeviceSampleLocationsPropertiesEXT :: PhysicalDeviceSampleLocationsPropertiesEXT -> Extent2D
$sel:sampleLocationSampleCounts:PhysicalDeviceSampleLocationsPropertiesEXT :: PhysicalDeviceSampleLocationsPropertiesEXT
-> "samples" ::: SampleCountFlagBits
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLE_LOCATIONS_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
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 PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlags)) ("samples" ::: SampleCountFlagBits
sampleLocationSampleCounts)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D)) (Extent2D
maxSampleLocationGridSize)
let pSampleLocationCoordinateRange' :: Ptr CFloat
pSampleLocationCoordinateRange' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr (FixedArray 2 CFloat)))
case ((Float, Float)
sampleLocationCoordinateRange) of
(Float
e0, Float
e1) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pSampleLocationCoordinateRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pSampleLocationCoordinateRange' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (Word32
sampleLocationSubPixelBits)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variableSampleLocations))
IO b
f
cStructSize :: Int
cStructSize = Int
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceSampleLocationsPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLE_LOCATIONS_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
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 PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
let pSampleLocationCoordinateRange' :: Ptr CFloat
pSampleLocationCoordinateRange' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr (FixedArray 2 CFloat)))
case ((forall a. Zero a => a
zero, forall a. Zero a => a
zero)) of
(Float
e0, Float
e1) -> do
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pSampleLocationCoordinateRange' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pSampleLocationCoordinateRange' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceSampleLocationsPropertiesEXT where
peekCStruct :: Ptr PhysicalDeviceSampleLocationsPropertiesEXT
-> IO PhysicalDeviceSampleLocationsPropertiesEXT
peekCStruct Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p = do
"samples" ::: SampleCountFlagBits
sampleLocationSampleCounts <- forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SampleCountFlags))
Extent2D
maxSampleLocationGridSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Extent2D))
let psampleLocationCoordinateRange :: Ptr CFloat
psampleLocationCoordinateRange = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr (FixedArray 2 CFloat)))
CFloat
sampleLocationCoordinateRange0 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
psampleLocationCoordinateRange forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
0 :: Ptr CFloat))
CFloat
sampleLocationCoordinateRange1 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
psampleLocationCoordinateRange forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
4 :: Ptr CFloat))
Word32
sampleLocationSubPixelBits <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32))
Bool32
variableSampleLocations <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSampleLocationsPropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("samples" ::: SampleCountFlagBits)
-> Extent2D
-> (Float, Float)
-> Word32
-> Bool
-> PhysicalDeviceSampleLocationsPropertiesEXT
PhysicalDeviceSampleLocationsPropertiesEXT
"samples" ::: SampleCountFlagBits
sampleLocationSampleCounts
Extent2D
maxSampleLocationGridSize
(( (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
sampleLocationCoordinateRange0)
, (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
sampleLocationCoordinateRange1) ))
Word32
sampleLocationSubPixelBits
(Bool32 -> Bool
bool32ToBool Bool32
variableSampleLocations)
instance Storable PhysicalDeviceSampleLocationsPropertiesEXT where
sizeOf :: PhysicalDeviceSampleLocationsPropertiesEXT -> Int
sizeOf ~PhysicalDeviceSampleLocationsPropertiesEXT
_ = Int
48
alignment :: PhysicalDeviceSampleLocationsPropertiesEXT -> Int
alignment ~PhysicalDeviceSampleLocationsPropertiesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceSampleLocationsPropertiesEXT
-> IO PhysicalDeviceSampleLocationsPropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceSampleLocationsPropertiesEXT
-> PhysicalDeviceSampleLocationsPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceSampleLocationsPropertiesEXT
ptr PhysicalDeviceSampleLocationsPropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSampleLocationsPropertiesEXT
ptr PhysicalDeviceSampleLocationsPropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceSampleLocationsPropertiesEXT where
zero :: PhysicalDeviceSampleLocationsPropertiesEXT
zero = ("samples" ::: SampleCountFlagBits)
-> Extent2D
-> (Float, Float)
-> Word32
-> Bool
-> PhysicalDeviceSampleLocationsPropertiesEXT
PhysicalDeviceSampleLocationsPropertiesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
(forall a. Zero a => a
zero, forall a. Zero a => a
zero)
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data MultisamplePropertiesEXT = MultisamplePropertiesEXT
{
MultisamplePropertiesEXT -> Extent2D
maxSampleLocationGridSize :: Extent2D }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MultisamplePropertiesEXT)
#endif
deriving instance Show MultisamplePropertiesEXT
instance ToCStruct MultisamplePropertiesEXT where
withCStruct :: forall b.
MultisamplePropertiesEXT
-> (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO b)
-> IO b
withCStruct MultisamplePropertiesEXT
x ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p MultisamplePropertiesEXT
x (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT) -> IO b
f "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p)
pokeCStruct :: forall b.
("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> MultisamplePropertiesEXT -> IO b -> IO b
pokeCStruct "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p MultisamplePropertiesEXT{Extent2D
maxSampleLocationGridSize :: Extent2D
$sel:maxSampleLocationGridSize:MultisamplePropertiesEXT :: MultisamplePropertiesEXT -> Extent2D
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MULTISAMPLE_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
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 (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (Extent2D
maxSampleLocationGridSize)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO b -> IO b
pokeZeroCStruct "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MULTISAMPLE_PROPERTIES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
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 (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MultisamplePropertiesEXT where
peekCStruct :: ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO MultisamplePropertiesEXT
peekCStruct "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p = do
Extent2D
maxSampleLocationGridSize <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D (("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Extent2D))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Extent2D -> MultisamplePropertiesEXT
MultisamplePropertiesEXT
Extent2D
maxSampleLocationGridSize
instance Storable MultisamplePropertiesEXT where
sizeOf :: MultisamplePropertiesEXT -> Int
sizeOf ~MultisamplePropertiesEXT
_ = Int
24
alignment :: MultisamplePropertiesEXT -> Int
alignment ~MultisamplePropertiesEXT
_ = Int
8
peek :: ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> IO MultisamplePropertiesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT)
-> MultisamplePropertiesEXT -> IO ()
poke "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
ptr MultisamplePropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMultisampleProperties" ::: Ptr MultisamplePropertiesEXT
ptr MultisamplePropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MultisamplePropertiesEXT where
zero :: MultisamplePropertiesEXT
zero = Extent2D -> MultisamplePropertiesEXT
MultisamplePropertiesEXT
forall a. Zero a => a
zero
type EXT_SAMPLE_LOCATIONS_SPEC_VERSION = 1
pattern EXT_SAMPLE_LOCATIONS_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_SAMPLE_LOCATIONS_SPEC_VERSION :: forall a. Integral a => a
$mEXT_SAMPLE_LOCATIONS_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SAMPLE_LOCATIONS_SPEC_VERSION = 1
type EXT_SAMPLE_LOCATIONS_EXTENSION_NAME = "VK_EXT_sample_locations"
pattern EXT_SAMPLE_LOCATIONS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_SAMPLE_LOCATIONS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_SAMPLE_LOCATIONS_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SAMPLE_LOCATIONS_EXTENSION_NAME = "VK_EXT_sample_locations"