{-# language CPP #-}
-- | = Name
--
-- VK_SEC_amigo_profiling - device extension
--
-- == VK_SEC_amigo_profiling
--
-- [__Name String__]
--     @VK_SEC_amigo_profiling@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     486
--
-- [__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__]
--
--     -   Ralph Potter <<data:image/png;base64, GitLab>>r_potter
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2022-07-29
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Ralph Potter, Samsung
--
--     -   Sangrak Oh, Samsung
--
--     -   Jinku Kang, Samsung
--
-- == Description
--
-- This extension is intended to communicate information from layered API
-- implementations such as ANGLE to internal proprietary system schedulers.
-- It has no behavioural implications beyond enabling more intelligent
-- behaviour from the system scheduler.
--
-- Application developers should avoid using this extension. It is
-- documented solely for the benefit of tools and layer developers, who may
-- need to manipulate @pNext@ chains that include these structures.
--
-- Note
--
-- There is currently no specification language written for this extension.
-- The links to APIs defined by the extension are to stubs that only
-- include generated content such as API declarations and implicit valid
-- usage statements.
--
-- Note
--
-- This extension is only intended for use in specific embedded
-- environments with known implementation details, and is therefore
-- undocumented.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceAmigoProfilingFeaturesSEC'
--
-- -   Extending 'Vulkan.Core10.Queue.SubmitInfo':
--
--     -   'AmigoProfilingSubmitInfoSEC'
--
-- == New Enum Constants
--
-- -   'SEC_AMIGO_PROFILING_EXTENSION_NAME'
--
-- -   'SEC_AMIGO_PROFILING_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_AMIGO_PROFILING_SUBMIT_INFO_SEC'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_AMIGO_PROFILING_FEATURES_SEC'
--
-- == Stub API References
--
-- There is currently no specification language written for this type. This
-- section acts only as placeholder and to avoid dead links in the
-- specification and reference pages.
--
-- > // Provided by VK_SEC_amigo_profiling
-- > typedef struct VkPhysicalDeviceAmigoProfilingFeaturesSEC {
-- >     VkStructureType    sType;
-- >     void*              pNext;
-- >     VkBool32           amigoProfiling;
-- > } VkPhysicalDeviceAmigoProfilingFeaturesSEC;
--
-- === Valid Usage (Implicit)
--
-- -   #VUID-VkPhysicalDeviceAmigoProfilingFeaturesSEC-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_AMIGO_PROFILING_FEATURES_SEC'
--
-- There is currently no specification language written for this type. This
-- section acts only as placeholder and to avoid dead links in the
-- specification and reference pages.
--
-- > // Provided by VK_SEC_amigo_profiling
-- > typedef struct VkAmigoProfilingSubmitInfoSEC {
-- >     VkStructureType    sType;
-- >     const void*        pNext;
-- >     uint64_t           firstDrawTimestamp;
-- >     uint64_t           swapBufferTimestamp;
-- > } VkAmigoProfilingSubmitInfoSEC;
--
-- === Valid Usage (Implicit)
--
-- -   #VUID-VkAmigoProfilingSubmitInfoSEC-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_AMIGO_PROFILING_SUBMIT_INFO_SEC'
--
-- == Version History
--
-- -   Revision 1, 2022-07-29 (Ralph Potter)
--
--     -   Initial specification
--
-- == See Also
--
-- 'AmigoProfilingSubmitInfoSEC', 'PhysicalDeviceAmigoProfilingFeaturesSEC'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_SEC_amigo_profiling Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_SEC_amigo_profiling  ( PhysicalDeviceAmigoProfilingFeaturesSEC(..)
                                                 , AmigoProfilingSubmitInfoSEC(..)
                                                 , SEC_AMIGO_PROFILING_SPEC_VERSION
                                                 , pattern SEC_AMIGO_PROFILING_SPEC_VERSION
                                                 , SEC_AMIGO_PROFILING_EXTENSION_NAME
                                                 , pattern SEC_AMIGO_PROFILING_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.Word (Word64)
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_AMIGO_PROFILING_SUBMIT_INFO_SEC))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_AMIGO_PROFILING_FEATURES_SEC))
-- | VkPhysicalDeviceAmigoProfilingFeaturesSEC - Stub description of
-- VkPhysicalDeviceAmigoProfilingFeaturesSEC
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_SEC_amigo_profiling VK_SEC_amigo_profiling>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceAmigoProfilingFeaturesSEC = PhysicalDeviceAmigoProfilingFeaturesSEC
  { -- No documentation found for Nested "VkPhysicalDeviceAmigoProfilingFeaturesSEC" "amigoProfiling"
    PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
amigoProfiling :: Bool }
  deriving (Typeable, PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
$c/= :: PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
== :: PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
$c== :: PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceAmigoProfilingFeaturesSEC)
#endif
deriving instance Show PhysicalDeviceAmigoProfilingFeaturesSEC

instance ToCStruct PhysicalDeviceAmigoProfilingFeaturesSEC where
  withCStruct :: forall b.
PhysicalDeviceAmigoProfilingFeaturesSEC
-> (Ptr PhysicalDeviceAmigoProfilingFeaturesSEC -> IO b) -> IO b
withCStruct PhysicalDeviceAmigoProfilingFeaturesSEC
x Ptr PhysicalDeviceAmigoProfilingFeaturesSEC -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p PhysicalDeviceAmigoProfilingFeaturesSEC
x (Ptr PhysicalDeviceAmigoProfilingFeaturesSEC -> IO b
f Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
-> PhysicalDeviceAmigoProfilingFeaturesSEC -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p PhysicalDeviceAmigoProfilingFeaturesSEC{Bool
amigoProfiling :: Bool
$sel:amigoProfiling:PhysicalDeviceAmigoProfilingFeaturesSEC :: PhysicalDeviceAmigoProfilingFeaturesSEC -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_AMIGO_PROFILING_FEATURES_SEC)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
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 PhysicalDeviceAmigoProfilingFeaturesSEC
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
amigoProfiling))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceAmigoProfilingFeaturesSEC -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_AMIGO_PROFILING_FEATURES_SEC)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
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 PhysicalDeviceAmigoProfilingFeaturesSEC
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 PhysicalDeviceAmigoProfilingFeaturesSEC where
  peekCStruct :: Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
-> IO PhysicalDeviceAmigoProfilingFeaturesSEC
peekCStruct Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
p = do
    Bool32
amigoProfiling <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceAmigoProfilingFeaturesSEC
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 -> PhysicalDeviceAmigoProfilingFeaturesSEC
PhysicalDeviceAmigoProfilingFeaturesSEC
             (Bool32 -> Bool
bool32ToBool Bool32
amigoProfiling)

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

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


-- | VkAmigoProfilingSubmitInfoSEC - Stub description of
-- VkAmigoProfilingSubmitInfoSEC
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_SEC_amigo_profiling VK_SEC_amigo_profiling>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AmigoProfilingSubmitInfoSEC = AmigoProfilingSubmitInfoSEC
  { -- No documentation found for Nested "VkAmigoProfilingSubmitInfoSEC" "firstDrawTimestamp"
    AmigoProfilingSubmitInfoSEC -> Word64
firstDrawTimestamp :: Word64
  , -- No documentation found for Nested "VkAmigoProfilingSubmitInfoSEC" "swapBufferTimestamp"
    AmigoProfilingSubmitInfoSEC -> Word64
swapBufferTimestamp :: Word64
  }
  deriving (Typeable, AmigoProfilingSubmitInfoSEC -> AmigoProfilingSubmitInfoSEC -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AmigoProfilingSubmitInfoSEC -> AmigoProfilingSubmitInfoSEC -> Bool
$c/= :: AmigoProfilingSubmitInfoSEC -> AmigoProfilingSubmitInfoSEC -> Bool
== :: AmigoProfilingSubmitInfoSEC -> AmigoProfilingSubmitInfoSEC -> Bool
$c== :: AmigoProfilingSubmitInfoSEC -> AmigoProfilingSubmitInfoSEC -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AmigoProfilingSubmitInfoSEC)
#endif
deriving instance Show AmigoProfilingSubmitInfoSEC

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

instance FromCStruct AmigoProfilingSubmitInfoSEC where
  peekCStruct :: Ptr AmigoProfilingSubmitInfoSEC -> IO AmigoProfilingSubmitInfoSEC
peekCStruct Ptr AmigoProfilingSubmitInfoSEC
p = do
    Word64
firstDrawTimestamp <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AmigoProfilingSubmitInfoSEC
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
    Word64
swapBufferTimestamp <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AmigoProfilingSubmitInfoSEC
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> Word64 -> AmigoProfilingSubmitInfoSEC
AmigoProfilingSubmitInfoSEC
             Word64
firstDrawTimestamp Word64
swapBufferTimestamp

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

instance Zero AmigoProfilingSubmitInfoSEC where
  zero :: AmigoProfilingSubmitInfoSEC
zero = Word64 -> Word64 -> AmigoProfilingSubmitInfoSEC
AmigoProfilingSubmitInfoSEC
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


type SEC_AMIGO_PROFILING_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_SEC_AMIGO_PROFILING_SPEC_VERSION"
pattern SEC_AMIGO_PROFILING_SPEC_VERSION :: forall a . Integral a => a
pattern $bSEC_AMIGO_PROFILING_SPEC_VERSION :: forall a. Integral a => a
$mSEC_AMIGO_PROFILING_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
SEC_AMIGO_PROFILING_SPEC_VERSION = 1


type SEC_AMIGO_PROFILING_EXTENSION_NAME = "VK_SEC_amigo_profiling"

-- No documentation found for TopLevel "VK_SEC_AMIGO_PROFILING_EXTENSION_NAME"
pattern SEC_AMIGO_PROFILING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bSEC_AMIGO_PROFILING_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mSEC_AMIGO_PROFILING_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
SEC_AMIGO_PROFILING_EXTENSION_NAME = "VK_SEC_amigo_profiling"