{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_pipeline_creation_cache_control  ( pattern ERROR_PIPELINE_COMPILE_REQUIRED_EXT
                                                                 , PhysicalDevicePipelineCreationCacheControlFeaturesEXT(..)
                                                                 , EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION
                                                                 , pattern EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION
                                                                 , EXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME
                                                                 , pattern EXT_PIPELINE_CREATION_CACHE_CONTROL_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.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.Result (Result(PIPELINE_COMPILE_REQUIRED_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_CREATION_CACHE_CONTROL_FEATURES_EXT))
-- No documentation found for TopLevel "VK_ERROR_PIPELINE_COMPILE_REQUIRED_EXT"
pattern $bERROR_PIPELINE_COMPILE_REQUIRED_EXT :: Result
$mERROR_PIPELINE_COMPILE_REQUIRED_EXT :: forall r. Result -> (Void# -> r) -> (Void# -> r) -> r
ERROR_PIPELINE_COMPILE_REQUIRED_EXT = PIPELINE_COMPILE_REQUIRED_EXT


-- | VkPhysicalDevicePipelineCreationCacheControlFeaturesEXT - Structure
-- describing whether pipeline cache control can be supported by an
-- implementation
--
-- = Members
--
-- The members of the
-- 'PhysicalDevicePipelineCreationCacheControlFeaturesEXT' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDevicePipelineCreationCacheControlFeaturesEXT' structure
-- is included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDevicePipelineCreationCacheControlFeaturesEXT' /can/ also be
-- used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- enable features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevicePipelineCreationCacheControlFeaturesEXT = PhysicalDevicePipelineCreationCacheControlFeaturesEXT
  { -- | @pipelineCreationCacheControl@ indicates that the implementation
    -- supports:
    --
    -- -   The following /can/ be used in @Vk*PipelineCreateInfo@::@flags@:
    --
    --     -   'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
    --
    --     -   'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT'
    --
    -- -   The following /can/ be used in
    --     'Vulkan.Core10.PipelineCache.PipelineCacheCreateInfo'::@flags@:
    --
    --     -   'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT'
    PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
pipelineCreationCacheControl :: Bool }
  deriving (Typeable, PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
(PhysicalDevicePipelineCreationCacheControlFeaturesEXT
 -> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool)
-> (PhysicalDevicePipelineCreationCacheControlFeaturesEXT
    -> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool)
-> Eq PhysicalDevicePipelineCreationCacheControlFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
$c/= :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
== :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
$c== :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePipelineCreationCacheControlFeaturesEXT)
#endif
deriving instance Show PhysicalDevicePipelineCreationCacheControlFeaturesEXT

instance ToCStruct PhysicalDevicePipelineCreationCacheControlFeaturesEXT where
  withCStruct :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> (Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
    -> IO b)
-> IO b
withCStruct x :: PhysicalDevicePipelineCreationCacheControlFeaturesEXT
x f :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
  -> IO b)
 -> IO b)
-> (Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p -> Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p PhysicalDevicePipelineCreationCacheControlFeaturesEXT
x (Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT -> IO b
f Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> IO b
-> IO b
pokeCStruct p :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p PhysicalDevicePipelineCreationCacheControlFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_CREATION_CACHE_CONTROL_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> 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 PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
pipelineCreationCacheControl))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_CREATION_CACHE_CONTROL_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> 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 PhysicalDevicePipelineCreationCacheControlFeaturesEXT
p Ptr PhysicalDevicePipelineCreationCacheControlFeaturesEXT
-> 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))
    IO b
f

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

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

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


type EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION = 3

-- No documentation found for TopLevel "VK_EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION"
pattern EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION :: a
$mEXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_PIPELINE_CREATION_CACHE_CONTROL_SPEC_VERSION = 3


type EXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME = "VK_EXT_pipeline_creation_cache_control"

-- No documentation found for TopLevel "VK_EXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME"
pattern EXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME :: a
$mEXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_PIPELINE_CREATION_CACHE_CONTROL_EXTENSION_NAME = "VK_EXT_pipeline_creation_cache_control"