{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_filter_cubic  ( pattern FILTER_CUBIC_EXT
                                              , pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT
                                              , PhysicalDeviceImageViewImageFormatInfoEXT(..)
                                              , FilterCubicImageViewImageFormatPropertiesEXT(..)
                                              , EXT_FILTER_CUBIC_SPEC_VERSION
                                              , pattern EXT_FILTER_CUBIC_SPEC_VERSION
                                              , EXT_FILTER_CUBIC_EXTENSION_NAME
                                              , pattern EXT_FILTER_CUBIC_EXTENSION_NAME
                                              ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageViewType (ImageViewType)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.Filter (Filter(FILTER_CUBIC_IMG))
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlags)
import Vulkan.Core10.Enums.FormatFeatureFlagBits (FormatFeatureFlagBits(FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_IMAGE_FORMAT_INFO_EXT))
-- No documentation found for TopLevel "VK_FILTER_CUBIC_EXT"
pattern $bFILTER_CUBIC_EXT :: Filter
$mFILTER_CUBIC_EXT :: forall r. Filter -> (Void# -> r) -> (Void# -> r) -> r
FILTER_CUBIC_EXT = FILTER_CUBIC_IMG


-- No documentation found for TopLevel "VK_FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT"
pattern $bFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT :: FormatFeatureFlagBits
$mFORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT :: forall r.
FormatFeatureFlagBits -> (Void# -> r) -> (Void# -> r) -> r
FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT = FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG


-- | VkPhysicalDeviceImageViewImageFormatInfoEXT - Structure for providing
-- image view type
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceImageViewImageFormatInfoEXT = PhysicalDeviceImageViewImageFormatInfoEXT
  { -- | @imageViewType@ is a 'Vulkan.Core10.Enums.ImageViewType.ImageViewType'
    -- value specifying the type of the image view.
    --
    -- @imageViewType@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' value
    PhysicalDeviceImageViewImageFormatInfoEXT -> ImageViewType
imageViewType :: ImageViewType }
  deriving (Typeable, PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool
(PhysicalDeviceImageViewImageFormatInfoEXT
 -> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool)
-> (PhysicalDeviceImageViewImageFormatInfoEXT
    -> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool)
-> Eq PhysicalDeviceImageViewImageFormatInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool
$c/= :: PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool
== :: PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool
$c== :: PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageViewImageFormatInfoEXT)
#endif
deriving instance Show PhysicalDeviceImageViewImageFormatInfoEXT

instance ToCStruct PhysicalDeviceImageViewImageFormatInfoEXT where
  withCStruct :: PhysicalDeviceImageViewImageFormatInfoEXT
-> (Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceImageViewImageFormatInfoEXT
x f :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p -> Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p PhysicalDeviceImageViewImageFormatInfoEXT
x (Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b
f Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p PhysicalDeviceImageViewImageFormatInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_IMAGE_FORMAT_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ImageViewType -> ImageViewType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageViewType)) (ImageViewType
imageViewType)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_IMAGE_FORMAT_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ImageViewType -> ImageViewType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageViewType)) (ImageViewType
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceImageViewImageFormatInfoEXT where
  peekCStruct :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> IO PhysicalDeviceImageViewImageFormatInfoEXT
peekCStruct p :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p = do
    ImageViewType
imageViewType <- Ptr ImageViewType -> IO ImageViewType
forall a. Storable a => Ptr a -> IO a
peek @ImageViewType ((Ptr PhysicalDeviceImageViewImageFormatInfoEXT
p Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> Int -> Ptr ImageViewType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageViewType))
    PhysicalDeviceImageViewImageFormatInfoEXT
-> IO PhysicalDeviceImageViewImageFormatInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceImageViewImageFormatInfoEXT
 -> IO PhysicalDeviceImageViewImageFormatInfoEXT)
-> PhysicalDeviceImageViewImageFormatInfoEXT
-> IO PhysicalDeviceImageViewImageFormatInfoEXT
forall a b. (a -> b) -> a -> b
$ ImageViewType -> PhysicalDeviceImageViewImageFormatInfoEXT
PhysicalDeviceImageViewImageFormatInfoEXT
             ImageViewType
imageViewType

instance Storable PhysicalDeviceImageViewImageFormatInfoEXT where
  sizeOf :: PhysicalDeviceImageViewImageFormatInfoEXT -> Int
sizeOf ~PhysicalDeviceImageViewImageFormatInfoEXT
_ = 24
  alignment :: PhysicalDeviceImageViewImageFormatInfoEXT -> Int
alignment ~PhysicalDeviceImageViewImageFormatInfoEXT
_ = 8
  peek :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> IO PhysicalDeviceImageViewImageFormatInfoEXT
peek = Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> IO PhysicalDeviceImageViewImageFormatInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> IO ()
poke ptr :: Ptr PhysicalDeviceImageViewImageFormatInfoEXT
ptr poked :: PhysicalDeviceImageViewImageFormatInfoEXT
poked = Ptr PhysicalDeviceImageViewImageFormatInfoEXT
-> PhysicalDeviceImageViewImageFormatInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceImageViewImageFormatInfoEXT
ptr PhysicalDeviceImageViewImageFormatInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceImageViewImageFormatInfoEXT where
  zero :: PhysicalDeviceImageViewImageFormatInfoEXT
zero = ImageViewType -> PhysicalDeviceImageViewImageFormatInfoEXT
PhysicalDeviceImageViewImageFormatInfoEXT
           ImageViewType
forall a. Zero a => a
zero


-- | VkFilterCubicImageViewImageFormatPropertiesEXT - Structure for querying
-- cubic filtering capabilities of an image view type
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT'
--
-- == Valid Usage
--
-- -   If the @pNext@ chain of the
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.ImageFormatProperties2'
--     structure includes a 'FilterCubicImageViewImageFormatPropertiesEXT'
--     structure, the @pNext@ chain of the
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceImageFormatInfo2'
--     structure /must/ include a
--     'PhysicalDeviceImageViewImageFormatInfoEXT' structure with an
--     @imageViewType@ that is compatible with @imageType@
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data FilterCubicImageViewImageFormatPropertiesEXT = FilterCubicImageViewImageFormatPropertiesEXT
  { -- | @filterCubic@ tells if image format, image type and image view type
    -- /can/ be used with cubic filtering. This field is set by the
    -- implementation. User-specified value is ignored.
    FilterCubicImageViewImageFormatPropertiesEXT -> Bool
filterCubic :: Bool
  , -- | @filterCubicMinmax@ tells if image format, image type and image view
    -- type /can/ be used with cubic filtering and minmax filtering. This field
    -- is set by the implementation. User-specified value is ignored.
    FilterCubicImageViewImageFormatPropertiesEXT -> Bool
filterCubicMinmax :: Bool
  }
  deriving (Typeable, FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> Bool
(FilterCubicImageViewImageFormatPropertiesEXT
 -> FilterCubicImageViewImageFormatPropertiesEXT -> Bool)
-> (FilterCubicImageViewImageFormatPropertiesEXT
    -> FilterCubicImageViewImageFormatPropertiesEXT -> Bool)
-> Eq FilterCubicImageViewImageFormatPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> Bool
$c/= :: FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> Bool
== :: FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> Bool
$c== :: FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FilterCubicImageViewImageFormatPropertiesEXT)
#endif
deriving instance Show FilterCubicImageViewImageFormatPropertiesEXT

instance ToCStruct FilterCubicImageViewImageFormatPropertiesEXT where
  withCStruct :: FilterCubicImageViewImageFormatPropertiesEXT
-> (Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b)
-> IO b
withCStruct x :: FilterCubicImageViewImageFormatPropertiesEXT
x f :: Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
p -> Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr FilterCubicImageViewImageFormatPropertiesEXT
p FilterCubicImageViewImageFormatPropertiesEXT
x (Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b
f Ptr FilterCubicImageViewImageFormatPropertiesEXT
p)
  pokeCStruct :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
p FilterCubicImageViewImageFormatPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterCubic))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterCubicMinmax))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr FilterCubicImageViewImageFormatPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct FilterCubicImageViewImageFormatPropertiesEXT where
  peekCStruct :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> IO FilterCubicImageViewImageFormatPropertiesEXT
peekCStruct p :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
p = do
    Bool32
filterCubic <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
filterCubicMinmax <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr FilterCubicImageViewImageFormatPropertiesEXT
p Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    FilterCubicImageViewImageFormatPropertiesEXT
-> IO FilterCubicImageViewImageFormatPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilterCubicImageViewImageFormatPropertiesEXT
 -> IO FilterCubicImageViewImageFormatPropertiesEXT)
-> FilterCubicImageViewImageFormatPropertiesEXT
-> IO FilterCubicImageViewImageFormatPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> FilterCubicImageViewImageFormatPropertiesEXT
FilterCubicImageViewImageFormatPropertiesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
filterCubic) (Bool32 -> Bool
bool32ToBool Bool32
filterCubicMinmax)

instance Storable FilterCubicImageViewImageFormatPropertiesEXT where
  sizeOf :: FilterCubicImageViewImageFormatPropertiesEXT -> Int
sizeOf ~FilterCubicImageViewImageFormatPropertiesEXT
_ = 24
  alignment :: FilterCubicImageViewImageFormatPropertiesEXT -> Int
alignment ~FilterCubicImageViewImageFormatPropertiesEXT
_ = 8
  peek :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> IO FilterCubicImageViewImageFormatPropertiesEXT
peek = Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> IO FilterCubicImageViewImageFormatPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> IO ()
poke ptr :: Ptr FilterCubicImageViewImageFormatPropertiesEXT
ptr poked :: FilterCubicImageViewImageFormatPropertiesEXT
poked = Ptr FilterCubicImageViewImageFormatPropertiesEXT
-> FilterCubicImageViewImageFormatPropertiesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr FilterCubicImageViewImageFormatPropertiesEXT
ptr FilterCubicImageViewImageFormatPropertiesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero FilterCubicImageViewImageFormatPropertiesEXT where
  zero :: FilterCubicImageViewImageFormatPropertiesEXT
zero = Bool -> Bool -> FilterCubicImageViewImageFormatPropertiesEXT
FilterCubicImageViewImageFormatPropertiesEXT
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


type EXT_FILTER_CUBIC_SPEC_VERSION = 3

-- No documentation found for TopLevel "VK_EXT_FILTER_CUBIC_SPEC_VERSION"
pattern EXT_FILTER_CUBIC_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_FILTER_CUBIC_SPEC_VERSION :: a
$mEXT_FILTER_CUBIC_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_FILTER_CUBIC_SPEC_VERSION = 3


type EXT_FILTER_CUBIC_EXTENSION_NAME = "VK_EXT_filter_cubic"

-- No documentation found for TopLevel "VK_EXT_FILTER_CUBIC_EXTENSION_NAME"
pattern EXT_FILTER_CUBIC_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_FILTER_CUBIC_EXTENSION_NAME :: a
$mEXT_FILTER_CUBIC_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_FILTER_CUBIC_EXTENSION_NAME = "VK_EXT_filter_cubic"