{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_image_view_min_lod ( PhysicalDeviceImageViewMinLodFeaturesEXT(..)
, ImageViewMinLodCreateInfoEXT(..)
, EXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION
, pattern EXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION
, EXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME
, pattern EXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
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.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 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_IMAGE_VIEW_MIN_LOD_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_MIN_LOD_FEATURES_EXT))
data PhysicalDeviceImageViewMinLodFeaturesEXT = PhysicalDeviceImageViewMinLodFeaturesEXT
{
PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
minLod :: Bool }
deriving (Typeable, PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
$c/= :: PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
== :: PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
$c== :: PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageViewMinLodFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceImageViewMinLodFeaturesEXT
instance ToCStruct PhysicalDeviceImageViewMinLodFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceImageViewMinLodFeaturesEXT
-> (Ptr PhysicalDeviceImageViewMinLodFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceImageViewMinLodFeaturesEXT
x Ptr PhysicalDeviceImageViewMinLodFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p PhysicalDeviceImageViewMinLodFeaturesEXT
x (Ptr PhysicalDeviceImageViewMinLodFeaturesEXT -> IO b
f Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p PhysicalDeviceImageViewMinLodFeaturesEXT{Bool
minLod :: Bool
$sel:minLod:PhysicalDeviceImageViewMinLodFeaturesEXT :: PhysicalDeviceImageViewMinLodFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_MIN_LOD_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
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 PhysicalDeviceImageViewMinLodFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
minLod))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceImageViewMinLodFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_MIN_LOD_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
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 PhysicalDeviceImageViewMinLodFeaturesEXT
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 PhysicalDeviceImageViewMinLodFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
-> IO PhysicalDeviceImageViewMinLodFeaturesEXT
peekCStruct Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
p = do
Bool32
minLod <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
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 -> PhysicalDeviceImageViewMinLodFeaturesEXT
PhysicalDeviceImageViewMinLodFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
minLod)
instance Storable PhysicalDeviceImageViewMinLodFeaturesEXT where
sizeOf :: PhysicalDeviceImageViewMinLodFeaturesEXT -> Int
sizeOf ~PhysicalDeviceImageViewMinLodFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceImageViewMinLodFeaturesEXT -> Int
alignment ~PhysicalDeviceImageViewMinLodFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
-> IO PhysicalDeviceImageViewMinLodFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
-> PhysicalDeviceImageViewMinLodFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
ptr PhysicalDeviceImageViewMinLodFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageViewMinLodFeaturesEXT
ptr PhysicalDeviceImageViewMinLodFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceImageViewMinLodFeaturesEXT where
zero :: PhysicalDeviceImageViewMinLodFeaturesEXT
zero = Bool -> PhysicalDeviceImageViewMinLodFeaturesEXT
PhysicalDeviceImageViewMinLodFeaturesEXT
forall a. Zero a => a
zero
data ImageViewMinLodCreateInfoEXT = ImageViewMinLodCreateInfoEXT
{
ImageViewMinLodCreateInfoEXT -> Float
minLod :: Float }
deriving (Typeable, ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> Bool
$c/= :: ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> Bool
== :: ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> Bool
$c== :: ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageViewMinLodCreateInfoEXT)
#endif
deriving instance Show ImageViewMinLodCreateInfoEXT
instance ToCStruct ImageViewMinLodCreateInfoEXT where
withCStruct :: forall b.
ImageViewMinLodCreateInfoEXT
-> (Ptr ImageViewMinLodCreateInfoEXT -> IO b) -> IO b
withCStruct ImageViewMinLodCreateInfoEXT
x Ptr ImageViewMinLodCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ImageViewMinLodCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewMinLodCreateInfoEXT
p ImageViewMinLodCreateInfoEXT
x (Ptr ImageViewMinLodCreateInfoEXT -> IO b
f Ptr ImageViewMinLodCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr ImageViewMinLodCreateInfoEXT
p ImageViewMinLodCreateInfoEXT{Float
minLod :: Float
$sel:minLod:ImageViewMinLodCreateInfoEXT :: ImageViewMinLodCreateInfoEXT -> Float
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewMinLodCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_MIN_LOD_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewMinLodCreateInfoEXT
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 ImageViewMinLodCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minLod))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ImageViewMinLodCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr ImageViewMinLodCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewMinLodCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_VIEW_MIN_LOD_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageViewMinLodCreateInfoEXT
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 ImageViewMinLodCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct ImageViewMinLodCreateInfoEXT where
peekCStruct :: Ptr ImageViewMinLodCreateInfoEXT -> IO ImageViewMinLodCreateInfoEXT
peekCStruct Ptr ImageViewMinLodCreateInfoEXT
p = do
CFloat
minLod <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr ImageViewMinLodCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CFloat))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Float -> ImageViewMinLodCreateInfoEXT
ImageViewMinLodCreateInfoEXT
(coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
minLod)
instance Storable ImageViewMinLodCreateInfoEXT where
sizeOf :: ImageViewMinLodCreateInfoEXT -> Int
sizeOf ~ImageViewMinLodCreateInfoEXT
_ = Int
24
alignment :: ImageViewMinLodCreateInfoEXT -> Int
alignment ~ImageViewMinLodCreateInfoEXT
_ = Int
8
peek :: Ptr ImageViewMinLodCreateInfoEXT -> IO ImageViewMinLodCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImageViewMinLodCreateInfoEXT
-> ImageViewMinLodCreateInfoEXT -> IO ()
poke Ptr ImageViewMinLodCreateInfoEXT
ptr ImageViewMinLodCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageViewMinLodCreateInfoEXT
ptr ImageViewMinLodCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImageViewMinLodCreateInfoEXT where
zero :: ImageViewMinLodCreateInfoEXT
zero = Float -> ImageViewMinLodCreateInfoEXT
ImageViewMinLodCreateInfoEXT
forall a. Zero a => a
zero
type EXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION = 1
pattern EXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION :: forall a. Integral a => a
$mEXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_IMAGE_VIEW_MIN_LOD_SPEC_VERSION = 1
type EXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME = "VK_EXT_image_view_min_lod"
pattern EXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_IMAGE_VIEW_MIN_LOD_EXTENSION_NAME = "VK_EXT_image_view_min_lod"