{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_non_seamless_cube_map ( PhysicalDeviceNonSeamlessCubeMapFeaturesEXT(..)
, EXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION
, pattern EXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION
, EXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME
, pattern EXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_NON_SEAMLESS_CUBE_MAP_FEATURES_EXT))
data PhysicalDeviceNonSeamlessCubeMapFeaturesEXT = PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
{
PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
nonSeamlessCubeMap :: Bool }
deriving (Typeable, PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
$c/= :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
== :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
$c== :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceNonSeamlessCubeMapFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
instance ToCStruct PhysicalDeviceNonSeamlessCubeMapFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> (Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
x Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
x (Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO b
f Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p PhysicalDeviceNonSeamlessCubeMapFeaturesEXT{Bool
nonSeamlessCubeMap :: Bool
$sel:nonSeamlessCubeMap:PhysicalDeviceNonSeamlessCubeMapFeaturesEXT :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NON_SEAMLESS_CUBE_MAP_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
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 PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nonSeamlessCubeMap))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_NON_SEAMLESS_CUBE_MAP_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
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 PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
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 PhysicalDeviceNonSeamlessCubeMapFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> IO PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
peekCStruct Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
p = do
Bool32
nonSeamlessCubeMap <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
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 -> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
nonSeamlessCubeMap)
instance Storable PhysicalDeviceNonSeamlessCubeMapFeaturesEXT where
sizeOf :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Int
sizeOf ~PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> Int
alignment ~PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> IO PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
-> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
ptr PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceNonSeamlessCubeMapFeaturesEXT where
zero :: PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
zero = Bool -> PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
PhysicalDeviceNonSeamlessCubeMapFeaturesEXT
forall a. Zero a => a
zero
type EXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION = 1
pattern EXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION :: forall a. Integral a => a
$mEXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_NON_SEAMLESS_CUBE_MAP_SPEC_VERSION = 1
type EXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME = "VK_EXT_non_seamless_cube_map"
pattern EXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_NON_SEAMLESS_CUBE_MAP_EXTENSION_NAME = "VK_EXT_non_seamless_cube_map"