{-# language CPP #-}
-- | = Name
--
-- VK_MSFT_layered_driver - device extension
--
-- == VK_MSFT_layered_driver
--
-- [__Name String__]
--     @VK_MSFT_layered_driver@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     531
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_physical_device_properties2 VK_KHR_get_physical_device_properties2>
--
-- [__Contact__]
--
--     -   Jesse Natalie
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_MSFT_layered_driver] @jenatali%0A*Here describe the issue or question you have about the VK_MSFT_layered_driver extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_MSFT_layered_driver.adoc VK_MSFT_layered_driver>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2023-06-21
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Jesse Natalie, Microsoft
--
-- == Description
--
-- This extension adds new physical device properties to allow applications
-- and the Vulkan ICD loader to understand when a physical device is
-- implemented as a layered driver on top of another underlying API.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceLayeredDriverPropertiesMSFT'
--
-- == New Enums
--
-- -   'LayeredDriverUnderlyingApiMSFT'
--
-- == New Enum Constants
--
-- -   'MSFT_LAYERED_DRIVER_EXTENSION_NAME'
--
-- -   'MSFT_LAYERED_DRIVER_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_LAYERED_DRIVER_PROPERTIES_MSFT'
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2023-06-21 (Jesse Natalie)
--
--     -   Initial revision
--
-- == See Also
--
-- 'LayeredDriverUnderlyingApiMSFT',
-- 'PhysicalDeviceLayeredDriverPropertiesMSFT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_MSFT_layered_driver Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_MSFT_layered_driver  ( PhysicalDeviceLayeredDriverPropertiesMSFT(..)
                                                 , LayeredDriverUnderlyingApiMSFT( LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT
                                                                                 , LAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT
                                                                                 , ..
                                                                                 )
                                                 , MSFT_LAYERED_DRIVER_SPEC_VERSION
                                                 , pattern MSFT_LAYERED_DRIVER_SPEC_VERSION
                                                 , MSFT_LAYERED_DRIVER_EXTENSION_NAME
                                                 , pattern MSFT_LAYERED_DRIVER_EXTENSION_NAME
                                                 ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
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 Data.Int (Int32)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_LAYERED_DRIVER_PROPERTIES_MSFT))
-- | VkPhysicalDeviceLayeredDriverPropertiesMSFT - Structure containing
-- information about driver layering for a physical device
--
-- = Description
--
-- These are properties of the driver layering information of a physical
-- device.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_MSFT_layered_driver VK_MSFT_layered_driver>,
-- 'LayeredDriverUnderlyingApiMSFT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceLayeredDriverPropertiesMSFT = PhysicalDeviceLayeredDriverPropertiesMSFT
  { -- | @underlyingAPI@ is a 'LayeredDriverUnderlyingApiMSFT' value indicating
    -- which underlying API is used to implement the layered driver, or
    -- 'LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT' if the driver is not layered.
    PhysicalDeviceLayeredDriverPropertiesMSFT
-> LayeredDriverUnderlyingApiMSFT
underlyingAPI :: LayeredDriverUnderlyingApiMSFT }
  deriving (Typeable, PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> Bool
$c/= :: PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> Bool
== :: PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> Bool
$c== :: PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceLayeredDriverPropertiesMSFT)
#endif
deriving instance Show PhysicalDeviceLayeredDriverPropertiesMSFT

instance ToCStruct PhysicalDeviceLayeredDriverPropertiesMSFT where
  withCStruct :: forall b.
PhysicalDeviceLayeredDriverPropertiesMSFT
-> (Ptr PhysicalDeviceLayeredDriverPropertiesMSFT -> IO b) -> IO b
withCStruct PhysicalDeviceLayeredDriverPropertiesMSFT
x Ptr PhysicalDeviceLayeredDriverPropertiesMSFT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p PhysicalDeviceLayeredDriverPropertiesMSFT
x (Ptr PhysicalDeviceLayeredDriverPropertiesMSFT -> IO b
f Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p PhysicalDeviceLayeredDriverPropertiesMSFT{LayeredDriverUnderlyingApiMSFT
underlyingAPI :: LayeredDriverUnderlyingApiMSFT
$sel:underlyingAPI:PhysicalDeviceLayeredDriverPropertiesMSFT :: PhysicalDeviceLayeredDriverPropertiesMSFT
-> LayeredDriverUnderlyingApiMSFT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LAYERED_DRIVER_PROPERTIES_MSFT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
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 PhysicalDeviceLayeredDriverPropertiesMSFT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr LayeredDriverUnderlyingApiMSFT)) (LayeredDriverUnderlyingApiMSFT
underlyingAPI)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceLayeredDriverPropertiesMSFT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LAYERED_DRIVER_PROPERTIES_MSFT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLayeredDriverPropertiesMSFT
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 PhysicalDeviceLayeredDriverPropertiesMSFT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr LayeredDriverUnderlyingApiMSFT)) (forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero PhysicalDeviceLayeredDriverPropertiesMSFT where
  zero :: PhysicalDeviceLayeredDriverPropertiesMSFT
zero = LayeredDriverUnderlyingApiMSFT
-> PhysicalDeviceLayeredDriverPropertiesMSFT
PhysicalDeviceLayeredDriverPropertiesMSFT
           forall a. Zero a => a
zero


-- | VkLayeredDriverUnderlyingApiMSFT - Layered driver underlying APIs
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_MSFT_layered_driver VK_MSFT_layered_driver>,
-- 'PhysicalDeviceLayeredDriverPropertiesMSFT'
newtype LayeredDriverUnderlyingApiMSFT = LayeredDriverUnderlyingApiMSFT Int32
  deriving newtype (LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c/= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
== :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c== :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
Eq, Eq LayeredDriverUnderlyingApiMSFT
LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Ordering
LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> LayeredDriverUnderlyingApiMSFT
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> LayeredDriverUnderlyingApiMSFT
$cmin :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> LayeredDriverUnderlyingApiMSFT
max :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> LayeredDriverUnderlyingApiMSFT
$cmax :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> LayeredDriverUnderlyingApiMSFT
>= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c>= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
> :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c> :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
<= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c<= :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
< :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
$c< :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Bool
compare :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Ordering
$ccompare :: LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> Ordering
Ord, Ptr LayeredDriverUnderlyingApiMSFT
-> IO LayeredDriverUnderlyingApiMSFT
Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> IO LayeredDriverUnderlyingApiMSFT
Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
Ptr LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> IO ()
LayeredDriverUnderlyingApiMSFT -> Int
forall b. Ptr b -> Int -> IO LayeredDriverUnderlyingApiMSFT
forall b. Ptr b -> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> IO ()
$cpoke :: Ptr LayeredDriverUnderlyingApiMSFT
-> LayeredDriverUnderlyingApiMSFT -> IO ()
peek :: Ptr LayeredDriverUnderlyingApiMSFT
-> IO LayeredDriverUnderlyingApiMSFT
$cpeek :: Ptr LayeredDriverUnderlyingApiMSFT
-> IO LayeredDriverUnderlyingApiMSFT
pokeByteOff :: forall b. Ptr b -> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO LayeredDriverUnderlyingApiMSFT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO LayeredDriverUnderlyingApiMSFT
pokeElemOff :: Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
$cpokeElemOff :: Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> LayeredDriverUnderlyingApiMSFT -> IO ()
peekElemOff :: Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> IO LayeredDriverUnderlyingApiMSFT
$cpeekElemOff :: Ptr LayeredDriverUnderlyingApiMSFT
-> Int -> IO LayeredDriverUnderlyingApiMSFT
alignment :: LayeredDriverUnderlyingApiMSFT -> Int
$calignment :: LayeredDriverUnderlyingApiMSFT -> Int
sizeOf :: LayeredDriverUnderlyingApiMSFT -> Int
$csizeOf :: LayeredDriverUnderlyingApiMSFT -> Int
Storable, LayeredDriverUnderlyingApiMSFT
forall a. a -> Zero a
zero :: LayeredDriverUnderlyingApiMSFT
$czero :: LayeredDriverUnderlyingApiMSFT
Zero)

-- No documentation found for Nested "VkLayeredDriverUnderlyingApiMSFT" "VK_LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT"
pattern $bLAYERED_DRIVER_UNDERLYING_API_NONE_MSFT :: LayeredDriverUnderlyingApiMSFT
$mLAYERED_DRIVER_UNDERLYING_API_NONE_MSFT :: forall {r}.
LayeredDriverUnderlyingApiMSFT -> ((# #) -> r) -> ((# #) -> r) -> r
LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT = LayeredDriverUnderlyingApiMSFT 0

-- No documentation found for Nested "VkLayeredDriverUnderlyingApiMSFT" "VK_LAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT"
pattern $bLAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT :: LayeredDriverUnderlyingApiMSFT
$mLAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT :: forall {r}.
LayeredDriverUnderlyingApiMSFT -> ((# #) -> r) -> ((# #) -> r) -> r
LAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT = LayeredDriverUnderlyingApiMSFT 1

{-# COMPLETE
  LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT
  , LAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT ::
    LayeredDriverUnderlyingApiMSFT
  #-}

conNameLayeredDriverUnderlyingApiMSFT :: String
conNameLayeredDriverUnderlyingApiMSFT :: String
conNameLayeredDriverUnderlyingApiMSFT = String
"LayeredDriverUnderlyingApiMSFT"

enumPrefixLayeredDriverUnderlyingApiMSFT :: String
enumPrefixLayeredDriverUnderlyingApiMSFT :: String
enumPrefixLayeredDriverUnderlyingApiMSFT = String
"LAYERED_DRIVER_UNDERLYING_API_"

showTableLayeredDriverUnderlyingApiMSFT :: [(LayeredDriverUnderlyingApiMSFT, String)]
showTableLayeredDriverUnderlyingApiMSFT :: [(LayeredDriverUnderlyingApiMSFT, String)]
showTableLayeredDriverUnderlyingApiMSFT =
  [
    ( LayeredDriverUnderlyingApiMSFT
LAYERED_DRIVER_UNDERLYING_API_NONE_MSFT
    , String
"NONE_MSFT"
    )
  ,
    ( LayeredDriverUnderlyingApiMSFT
LAYERED_DRIVER_UNDERLYING_API_D3D12_MSFT
    , String
"D3D12_MSFT"
    )
  ]

instance Show LayeredDriverUnderlyingApiMSFT where
  showsPrec :: Int -> LayeredDriverUnderlyingApiMSFT -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixLayeredDriverUnderlyingApiMSFT
      [(LayeredDriverUnderlyingApiMSFT, String)]
showTableLayeredDriverUnderlyingApiMSFT
      String
conNameLayeredDriverUnderlyingApiMSFT
      (\(LayeredDriverUnderlyingApiMSFT Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read LayeredDriverUnderlyingApiMSFT where
  readPrec :: ReadPrec LayeredDriverUnderlyingApiMSFT
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixLayeredDriverUnderlyingApiMSFT
      [(LayeredDriverUnderlyingApiMSFT, String)]
showTableLayeredDriverUnderlyingApiMSFT
      String
conNameLayeredDriverUnderlyingApiMSFT
      Int32 -> LayeredDriverUnderlyingApiMSFT
LayeredDriverUnderlyingApiMSFT

type MSFT_LAYERED_DRIVER_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_MSFT_LAYERED_DRIVER_SPEC_VERSION"
pattern MSFT_LAYERED_DRIVER_SPEC_VERSION :: forall a . Integral a => a
pattern $bMSFT_LAYERED_DRIVER_SPEC_VERSION :: forall a. Integral a => a
$mMSFT_LAYERED_DRIVER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
MSFT_LAYERED_DRIVER_SPEC_VERSION = 1


type MSFT_LAYERED_DRIVER_EXTENSION_NAME = "VK_MSFT_layered_driver"

-- No documentation found for TopLevel "VK_MSFT_LAYERED_DRIVER_EXTENSION_NAME"
pattern MSFT_LAYERED_DRIVER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bMSFT_LAYERED_DRIVER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mMSFT_LAYERED_DRIVER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
MSFT_LAYERED_DRIVER_EXTENSION_NAME = "VK_MSFT_layered_driver"