{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_metal_surface  ( createMetalSurfaceEXT
                                               , MetalSurfaceCreateInfoEXT(..)
                                               , MetalSurfaceCreateFlagsEXT(..)
                                               , EXT_METAL_SURFACE_SPEC_VERSION
                                               , pattern EXT_METAL_SURFACE_SPEC_VERSION
                                               , EXT_METAL_SURFACE_EXTENSION_NAME
                                               , pattern EXT_METAL_SURFACE_EXTENSION_NAME
                                               , SurfaceKHR(..)
                                               , CAMetalLayer
                                               ) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
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.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Extensions.WSITypes (CAMetalLayer)
import Vulkan.Core10.BaseType (Flags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Dynamic (InstanceCmds(pVkCreateMetalSurfaceEXT))
import Vulkan.Core10.Handles (Instance_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SurfaceKHR)
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_METAL_SURFACE_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.WSITypes (CAMetalLayer)
import Vulkan.Extensions.Handles (SurfaceKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateMetalSurfaceEXT
  :: FunPtr (Ptr Instance_T -> Ptr MetalSurfaceCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result) -> Ptr Instance_T -> Ptr MetalSurfaceCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result
createMetalSurfaceEXT :: forall io . MonadIO io => Instance -> MetalSurfaceCreateInfoEXT -> ("allocator" ::: Maybe AllocationCallbacks) -> io (SurfaceKHR)
createMetalSurfaceEXT :: Instance
-> MetalSurfaceCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SurfaceKHR
createMetalSurfaceEXT instance' :: Instance
instance' createInfo :: MetalSurfaceCreateInfoEXT
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO SurfaceKHR -> io SurfaceKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SurfaceKHR -> io SurfaceKHR)
-> (ContT SurfaceKHR IO SurfaceKHR -> IO SurfaceKHR)
-> ContT SurfaceKHR IO SurfaceKHR
-> io SurfaceKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT SurfaceKHR IO SurfaceKHR -> IO SurfaceKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT SurfaceKHR IO SurfaceKHR -> io SurfaceKHR)
-> ContT SurfaceKHR IO SurfaceKHR -> io SurfaceKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateMetalSurfaceEXTPtr :: FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateMetalSurfaceEXTPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
pVkCreateMetalSurfaceEXT (Instance -> InstanceCmds
instanceCmds (Instance
instance' :: Instance))
  IO () -> ContT SurfaceKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SurfaceKHR IO ())
-> IO () -> ContT SurfaceKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateMetalSurfaceEXTPtr FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateMetalSurfaceEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateMetalSurfaceEXT' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateMetalSurfaceEXT' = FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
mkVkCreateMetalSurfaceEXT FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateMetalSurfaceEXTPtr
  "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
pCreateInfo <- ((("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
  -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT
     SurfaceKHR IO ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
   -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT
      SurfaceKHR IO ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT))
-> ((("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
     -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT
     SurfaceKHR IO ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
forall a b. (a -> b) -> a -> b
$ MetalSurfaceCreateInfoEXT
-> (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
    -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MetalSurfaceCreateInfoEXT
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pSurface" ::: Ptr SurfaceKHR
pPSurface <- ((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR))
-> ((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pSurface" ::: Ptr SurfaceKHR)
-> (("pSurface" ::: Ptr SurfaceKHR) -> IO ())
-> (("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSurface" ::: Ptr SurfaceKHR)
forall a. Int -> IO (Ptr a)
callocBytes @SurfaceKHR 8) ("pSurface" ::: Ptr SurfaceKHR) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT SurfaceKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT SurfaceKHR IO Result)
-> IO Result -> ContT SurfaceKHR IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateMetalSurfaceEXT' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pSurface" ::: Ptr SurfaceKHR
pPSurface)
  IO () -> ContT SurfaceKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SurfaceKHR IO ())
-> IO () -> ContT SurfaceKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  SurfaceKHR
pSurface <- IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR)
-> IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall a b. (a -> b) -> a -> b
$ ("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR
forall a. Storable a => Ptr a -> IO a
peek @SurfaceKHR "pSurface" ::: Ptr SurfaceKHR
pPSurface
  SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR)
-> SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall a b. (a -> b) -> a -> b
$ (SurfaceKHR
pSurface)
data MetalSurfaceCreateInfoEXT = MetalSurfaceCreateInfoEXT
  { 
    MetalSurfaceCreateInfoEXT -> MetalSurfaceCreateFlagsEXT
flags :: MetalSurfaceCreateFlagsEXT
  , 
    
    MetalSurfaceCreateInfoEXT -> Ptr CAMetalLayer
layer :: Ptr CAMetalLayer
  }
  deriving (Typeable)
deriving instance Show MetalSurfaceCreateInfoEXT
instance ToCStruct MetalSurfaceCreateInfoEXT where
  withCStruct :: MetalSurfaceCreateInfoEXT
-> (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b)
-> IO b
withCStruct x :: MetalSurfaceCreateInfoEXT
x f :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b
f = Int
-> Int
-> (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b)
 -> IO b)
-> (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p -> ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> MetalSurfaceCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p MetalSurfaceCreateInfoEXT
x (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b
f "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> MetalSurfaceCreateInfoEXT -> IO b -> IO b
pokeCStruct p :: "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p MetalSurfaceCreateInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_METAL_SURFACE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr MetalSurfaceCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr MetalSurfaceCreateFlagsEXT)) (MetalSurfaceCreateFlagsEXT
flags)
    Ptr (Ptr CAMetalLayer) -> Ptr CAMetalLayer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr (Ptr CAMetalLayer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr CAMetalLayer))) (Ptr CAMetalLayer
layer)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT) -> IO b -> IO b
pokeZeroCStruct p :: "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_METAL_SURFACE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr CAMetalLayer) -> Ptr CAMetalLayer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr (Ptr CAMetalLayer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr CAMetalLayer))) (Ptr CAMetalLayer
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct MetalSurfaceCreateInfoEXT where
  peekCStruct :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> IO MetalSurfaceCreateInfoEXT
peekCStruct p :: "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p = do
    MetalSurfaceCreateFlagsEXT
flags <- Ptr MetalSurfaceCreateFlagsEXT -> IO MetalSurfaceCreateFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @MetalSurfaceCreateFlagsEXT (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr MetalSurfaceCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr MetalSurfaceCreateFlagsEXT))
    Ptr CAMetalLayer
pLayer <- Ptr (Ptr CAMetalLayer) -> IO (Ptr CAMetalLayer)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CAMetalLayer) (("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
p ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> Int -> Ptr (Ptr CAMetalLayer)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr CAMetalLayer)))
    MetalSurfaceCreateInfoEXT -> IO MetalSurfaceCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetalSurfaceCreateInfoEXT -> IO MetalSurfaceCreateInfoEXT)
-> MetalSurfaceCreateInfoEXT -> IO MetalSurfaceCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ MetalSurfaceCreateFlagsEXT
-> Ptr CAMetalLayer -> MetalSurfaceCreateInfoEXT
MetalSurfaceCreateInfoEXT
             MetalSurfaceCreateFlagsEXT
flags Ptr CAMetalLayer
pLayer
instance Storable MetalSurfaceCreateInfoEXT where
  sizeOf :: MetalSurfaceCreateInfoEXT -> Int
sizeOf ~MetalSurfaceCreateInfoEXT
_ = 32
  alignment :: MetalSurfaceCreateInfoEXT -> Int
alignment ~MetalSurfaceCreateInfoEXT
_ = 8
  peek :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> IO MetalSurfaceCreateInfoEXT
peek = ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> IO MetalSurfaceCreateInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> MetalSurfaceCreateInfoEXT -> IO ()
poke ptr :: "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
ptr poked :: MetalSurfaceCreateInfoEXT
poked = ("pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT)
-> MetalSurfaceCreateInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr MetalSurfaceCreateInfoEXT
ptr MetalSurfaceCreateInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MetalSurfaceCreateInfoEXT where
  zero :: MetalSurfaceCreateInfoEXT
zero = MetalSurfaceCreateFlagsEXT
-> Ptr CAMetalLayer -> MetalSurfaceCreateInfoEXT
MetalSurfaceCreateInfoEXT
           MetalSurfaceCreateFlagsEXT
forall a. Zero a => a
zero
           Ptr CAMetalLayer
forall a. Zero a => a
zero
newtype MetalSurfaceCreateFlagsEXT = MetalSurfaceCreateFlagsEXT Flags
  deriving newtype (MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
(MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> Bool)
-> Eq MetalSurfaceCreateFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c/= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
== :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c== :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
Eq, Eq MetalSurfaceCreateFlagsEXT
Eq MetalSurfaceCreateFlagsEXT =>
(MetalSurfaceCreateFlagsEXT
 -> MetalSurfaceCreateFlagsEXT -> Ordering)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> Ord MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> Ordering
MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
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 :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$cmin :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
max :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$cmax :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
>= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c>= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
> :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c> :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
<= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c<= :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
< :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
$c< :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT -> Bool
compare :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> Ordering
$ccompare :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> Ordering
$cp1Ord :: Eq MetalSurfaceCreateFlagsEXT
Ord, Ptr b -> Int -> IO MetalSurfaceCreateFlagsEXT
Ptr b -> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
Ptr MetalSurfaceCreateFlagsEXT -> IO MetalSurfaceCreateFlagsEXT
Ptr MetalSurfaceCreateFlagsEXT
-> Int -> IO MetalSurfaceCreateFlagsEXT
Ptr MetalSurfaceCreateFlagsEXT
-> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
Ptr MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> IO ()
MetalSurfaceCreateFlagsEXT -> Int
(MetalSurfaceCreateFlagsEXT -> Int)
-> (MetalSurfaceCreateFlagsEXT -> Int)
-> (Ptr MetalSurfaceCreateFlagsEXT
    -> Int -> IO MetalSurfaceCreateFlagsEXT)
-> (Ptr MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO MetalSurfaceCreateFlagsEXT)
-> (forall b. Ptr b -> Int -> MetalSurfaceCreateFlagsEXT -> IO ())
-> (Ptr MetalSurfaceCreateFlagsEXT
    -> IO MetalSurfaceCreateFlagsEXT)
-> (Ptr MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> IO ())
-> Storable MetalSurfaceCreateFlagsEXT
forall b. Ptr b -> Int -> IO MetalSurfaceCreateFlagsEXT
forall b. Ptr b -> Int -> MetalSurfaceCreateFlagsEXT -> 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 MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> IO ()
$cpoke :: Ptr MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> IO ()
peek :: Ptr MetalSurfaceCreateFlagsEXT -> IO MetalSurfaceCreateFlagsEXT
$cpeek :: Ptr MetalSurfaceCreateFlagsEXT -> IO MetalSurfaceCreateFlagsEXT
pokeByteOff :: Ptr b -> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO MetalSurfaceCreateFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MetalSurfaceCreateFlagsEXT
pokeElemOff :: Ptr MetalSurfaceCreateFlagsEXT
-> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
$cpokeElemOff :: Ptr MetalSurfaceCreateFlagsEXT
-> Int -> MetalSurfaceCreateFlagsEXT -> IO ()
peekElemOff :: Ptr MetalSurfaceCreateFlagsEXT
-> Int -> IO MetalSurfaceCreateFlagsEXT
$cpeekElemOff :: Ptr MetalSurfaceCreateFlagsEXT
-> Int -> IO MetalSurfaceCreateFlagsEXT
alignment :: MetalSurfaceCreateFlagsEXT -> Int
$calignment :: MetalSurfaceCreateFlagsEXT -> Int
sizeOf :: MetalSurfaceCreateFlagsEXT -> Int
$csizeOf :: MetalSurfaceCreateFlagsEXT -> Int
Storable, MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT -> Zero MetalSurfaceCreateFlagsEXT
forall a. a -> Zero a
zero :: MetalSurfaceCreateFlagsEXT
$czero :: MetalSurfaceCreateFlagsEXT
Zero, Eq MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT
Eq MetalSurfaceCreateFlagsEXT =>
(MetalSurfaceCreateFlagsEXT
 -> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> MetalSurfaceCreateFlagsEXT
-> (Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT -> Int -> Bool)
-> (MetalSurfaceCreateFlagsEXT -> Maybe Int)
-> (MetalSurfaceCreateFlagsEXT -> Int)
-> (MetalSurfaceCreateFlagsEXT -> Bool)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT
    -> Int -> MetalSurfaceCreateFlagsEXT)
-> (MetalSurfaceCreateFlagsEXT -> Int)
-> Bits MetalSurfaceCreateFlagsEXT
Int -> MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT -> Bool
MetalSurfaceCreateFlagsEXT -> Int
MetalSurfaceCreateFlagsEXT -> Maybe Int
MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT -> Int -> Bool
MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: MetalSurfaceCreateFlagsEXT -> Int
$cpopCount :: MetalSurfaceCreateFlagsEXT -> Int
rotateR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$crotateR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
rotateL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$crotateL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
unsafeShiftR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cunsafeShiftR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
shiftR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cshiftR :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
unsafeShiftL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cunsafeShiftL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
shiftL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cshiftL :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
isSigned :: MetalSurfaceCreateFlagsEXT -> Bool
$cisSigned :: MetalSurfaceCreateFlagsEXT -> Bool
bitSize :: MetalSurfaceCreateFlagsEXT -> Int
$cbitSize :: MetalSurfaceCreateFlagsEXT -> Int
bitSizeMaybe :: MetalSurfaceCreateFlagsEXT -> Maybe Int
$cbitSizeMaybe :: MetalSurfaceCreateFlagsEXT -> Maybe Int
testBit :: MetalSurfaceCreateFlagsEXT -> Int -> Bool
$ctestBit :: MetalSurfaceCreateFlagsEXT -> Int -> Bool
complementBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$ccomplementBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
clearBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cclearBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
setBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$csetBit :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
bit :: Int -> MetalSurfaceCreateFlagsEXT
$cbit :: Int -> MetalSurfaceCreateFlagsEXT
zeroBits :: MetalSurfaceCreateFlagsEXT
$czeroBits :: MetalSurfaceCreateFlagsEXT
rotate :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$crotate :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
shift :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
$cshift :: MetalSurfaceCreateFlagsEXT -> Int -> MetalSurfaceCreateFlagsEXT
complement :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$ccomplement :: MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
xor :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$cxor :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
.|. :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$c.|. :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
.&. :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$c.&. :: MetalSurfaceCreateFlagsEXT
-> MetalSurfaceCreateFlagsEXT -> MetalSurfaceCreateFlagsEXT
$cp1Bits :: Eq MetalSurfaceCreateFlagsEXT
Bits)
instance Show MetalSurfaceCreateFlagsEXT where
  showsPrec :: Int -> MetalSurfaceCreateFlagsEXT -> ShowS
showsPrec p :: Int
p = \case
    MetalSurfaceCreateFlagsEXT x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "MetalSurfaceCreateFlagsEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read MetalSurfaceCreateFlagsEXT where
  readPrec :: ReadPrec MetalSurfaceCreateFlagsEXT
readPrec = ReadPrec MetalSurfaceCreateFlagsEXT
-> ReadPrec MetalSurfaceCreateFlagsEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec MetalSurfaceCreateFlagsEXT)]
-> ReadPrec MetalSurfaceCreateFlagsEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose []
                     ReadPrec MetalSurfaceCreateFlagsEXT
-> ReadPrec MetalSurfaceCreateFlagsEXT
-> ReadPrec MetalSurfaceCreateFlagsEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec MetalSurfaceCreateFlagsEXT
-> ReadPrec MetalSurfaceCreateFlagsEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "MetalSurfaceCreateFlagsEXT")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       MetalSurfaceCreateFlagsEXT -> ReadPrec MetalSurfaceCreateFlagsEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> MetalSurfaceCreateFlagsEXT
MetalSurfaceCreateFlagsEXT Flags
v)))
type EXT_METAL_SURFACE_SPEC_VERSION = 1
pattern EXT_METAL_SURFACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_METAL_SURFACE_SPEC_VERSION :: a
$mEXT_METAL_SURFACE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_METAL_SURFACE_SPEC_VERSION = 1
type EXT_METAL_SURFACE_EXTENSION_NAME = "VK_EXT_metal_surface"
pattern EXT_METAL_SURFACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_METAL_SURFACE_EXTENSION_NAME :: a
$mEXT_METAL_SURFACE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_METAL_SURFACE_EXTENSION_NAME = "VK_EXT_metal_surface"