{-# language CPP #-}
-- | = Name
--
-- VK_GGP_stream_descriptor_surface - instance extension
--
-- == VK_GGP_stream_descriptor_surface
--
-- [__Name String__]
--     @VK_GGP_stream_descriptor_surface@
--
-- [__Extension Type__]
--     Instance extension
--
-- [__Registered Extension Number__]
--     50
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_surface@
--
-- [__Contact__]
--
--     -   Jean-Francois Roy
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_GGP_stream_descriptor_surface] @jfroy%0A<<Here describe the issue or question you have about the VK_GGP_stream_descriptor_surface extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-01-28
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Jean-Francois Roy, Google
--
--     -   Brad Grantham, Google
--
--     -   Connor Smith, Google
--
--     -   Cort Stratton, Google
--
--     -   Hai Nguyen, Google
--
--     -   Ian Elliott, Google
--
--     -   Jesse Hall, Google
--
--     -   Jim Ray, Google
--
--     -   Katherine Wu, Google
--
--     -   Kaye Mason, Google
--
--     -   Kuangye Guo, Google
--
--     -   Mark Segal, Google
--
--     -   Nicholas Vining, Google
--
--     -   Paul Lalonde, Google
--
--     -   Richard O’Grady, Google
--
-- == Description
--
-- The @VK_GGP_stream_descriptor_surface@ extension is an instance
-- extension. It provides a mechanism to create a
-- 'Vulkan.Extensions.Handles.SurfaceKHR' object (defined by the
-- @VK_KHR_surface@ extension) that refers to a Google Games Platform
-- 'GgpStreamDescriptor'.
--
-- == New Commands
--
-- -   'createStreamDescriptorSurfaceGGP'
--
-- == New Structures
--
-- -   'StreamDescriptorSurfaceCreateInfoGGP'
--
-- == New Bitmasks
--
-- -   'StreamDescriptorSurfaceCreateFlagsGGP'
--
-- == New Enum Constants
--
-- -   'GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME'
--
-- -   'GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP'
--
-- == Version History
--
-- -   Revision 1, 2018-11-26 (Jean-Francois Roy)
--
--     -   Initial revision.
--
-- == See Also
--
-- 'StreamDescriptorSurfaceCreateFlagsGGP',
-- 'StreamDescriptorSurfaceCreateInfoGGP',
-- 'createStreamDescriptorSurfaceGGP'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_GGP_stream_descriptor_surface Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_GGP_stream_descriptor_surface  ( createStreamDescriptorSurfaceGGP
                                                           , StreamDescriptorSurfaceCreateInfoGGP(..)
                                                           , StreamDescriptorSurfaceCreateFlagsGGP(..)
                                                           , GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION
                                                           , pattern GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION
                                                           , GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME
                                                           , pattern GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME
                                                           , GgpStreamDescriptor
                                                           , SurfaceKHR(..)
                                                           ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
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.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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 Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (Instance(Instance))
import Vulkan.Dynamic (InstanceCmds(pVkCreateStreamDescriptorSurfaceGGP))
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.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateStreamDescriptorSurfaceGGP
  :: FunPtr (Ptr Instance_T -> Ptr StreamDescriptorSurfaceCreateInfoGGP -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result) -> Ptr Instance_T -> Ptr StreamDescriptorSurfaceCreateInfoGGP -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result

-- | vkCreateStreamDescriptorSurfaceGGP - Create a
-- 'Vulkan.Extensions.Handles.SurfaceKHR' object for a Google Games
-- Platform stream
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateStreamDescriptorSurfaceGGP-instance-parameter#
--     @instance@ /must/ be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkCreateStreamDescriptorSurfaceGGP-pCreateInfo-parameter#
--     @pCreateInfo@ /must/ be a valid pointer to a valid
--     'StreamDescriptorSurfaceCreateInfoGGP' structure
--
-- -   #VUID-vkCreateStreamDescriptorSurfaceGGP-pAllocator-parameter# If
--     @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid pointer
--     to a valid 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks'
--     structure
--
-- -   #VUID-vkCreateStreamDescriptorSurfaceGGP-pSurface-parameter#
--     @pSurface@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_NATIVE_WINDOW_IN_USE_KHR'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_GGP_stream_descriptor_surface VK_GGP_stream_descriptor_surface>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Instance',
-- 'StreamDescriptorSurfaceCreateInfoGGP',
-- 'Vulkan.Extensions.Handles.SurfaceKHR'
createStreamDescriptorSurfaceGGP :: forall io
                                  . (MonadIO io)
                                 => -- | @instance@ is the instance to associate with the surface.
                                    Instance
                                 -> -- | @pCreateInfo@ is a pointer to a 'StreamDescriptorSurfaceCreateInfoGGP'
                                    -- structure containing parameters that affect the creation of the surface
                                    -- object.
                                    StreamDescriptorSurfaceCreateInfoGGP
                                 -> -- | @pAllocator@ is the allocator used for host memory allocated for the
                                    -- surface object when there is no more specific allocator available (see
                                    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>).
                                    ("allocator" ::: Maybe AllocationCallbacks)
                                 -> io (SurfaceKHR)
createStreamDescriptorSurfaceGGP :: Instance
-> StreamDescriptorSurfaceCreateInfoGGP
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SurfaceKHR
createStreamDescriptorSurfaceGGP Instance
instance' StreamDescriptorSurfaceCreateInfoGGP
createInfo "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 vkCreateStreamDescriptorSurfaceGGPPtr :: FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
pVkCreateStreamDescriptorSurfaceGGP (case Instance
instance' of Instance{InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  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 StreamDescriptorSurfaceCreateInfoGGP)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> ("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 String
"" String
"The function pointer for vkCreateStreamDescriptorSurfaceGGP is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateStreamDescriptorSurfaceGGP' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateStreamDescriptorSurfaceGGP' = FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
mkVkCreateStreamDescriptorSurfaceGGP FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateStreamDescriptorSurfaceGGPPtr
  "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
pCreateInfo <- ((("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
  -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT
     SurfaceKHR
     IO
     ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
   -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT
      SurfaceKHR
      IO
      ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP))
-> ((("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
     -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT
     SurfaceKHR
     IO
     ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
forall a b. (a -> b) -> a -> b
$ StreamDescriptorSurfaceCreateInfoGGP
-> (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
    -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (StreamDescriptorSurfaceCreateInfoGGP
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
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 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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateStreamDescriptorSurfaceGGP" (Ptr Instance_T
-> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateStreamDescriptorSurfaceGGP' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
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)


-- | VkStreamDescriptorSurfaceCreateInfoGGP - Structure specifying parameters
-- of a newly created Google Games Platform stream surface object
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_GGP_stream_descriptor_surface VK_GGP_stream_descriptor_surface>,
-- 'StreamDescriptorSurfaceCreateFlagsGGP',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createStreamDescriptorSurfaceGGP'
data StreamDescriptorSurfaceCreateInfoGGP = StreamDescriptorSurfaceCreateInfoGGP
  { -- | @flags@ is reserved for future use.
    --
    -- #VUID-VkStreamDescriptorSurfaceCreateInfoGGP-flags-zerobitmask# @flags@
    -- /must/ be @0@
    StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
flags :: StreamDescriptorSurfaceCreateFlagsGGP
  , -- | @streamDescriptor@ is a 'GgpStreamDescriptor' referring to the GGP
    -- stream descriptor to associate with the surface.
    --
    -- #VUID-VkStreamDescriptorSurfaceCreateInfoGGP-streamDescriptor-02681#
    -- @streamDescriptor@ /must/ be a valid 'GgpStreamDescriptor'
    StreamDescriptorSurfaceCreateInfoGGP -> GgpStreamDescriptor
streamDescriptor :: GgpStreamDescriptor
  }
  deriving (Typeable, StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
(StreamDescriptorSurfaceCreateInfoGGP
 -> StreamDescriptorSurfaceCreateInfoGGP -> Bool)
-> (StreamDescriptorSurfaceCreateInfoGGP
    -> StreamDescriptorSurfaceCreateInfoGGP -> Bool)
-> Eq StreamDescriptorSurfaceCreateInfoGGP
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
$c/= :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
== :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
$c== :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateInfoGGP -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (StreamDescriptorSurfaceCreateInfoGGP)
#endif
deriving instance Show StreamDescriptorSurfaceCreateInfoGGP

instance ToCStruct StreamDescriptorSurfaceCreateInfoGGP where
  withCStruct :: StreamDescriptorSurfaceCreateInfoGGP
-> (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
    -> IO b)
-> IO b
withCStruct StreamDescriptorSurfaceCreateInfoGGP
x ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b
f = Int
-> (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
    -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
  -> IO b)
 -> IO b)
-> (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p -> ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> StreamDescriptorSurfaceCreateInfoGGP -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p StreamDescriptorSurfaceCreateInfoGGP
x (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b
f "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> StreamDescriptorSurfaceCreateInfoGGP -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p StreamDescriptorSurfaceCreateInfoGGP{GgpStreamDescriptor
StreamDescriptorSurfaceCreateFlagsGGP
streamDescriptor :: GgpStreamDescriptor
flags :: StreamDescriptorSurfaceCreateFlagsGGP
$sel:streamDescriptor:StreamDescriptorSurfaceCreateInfoGGP :: StreamDescriptorSurfaceCreateInfoGGP -> GgpStreamDescriptor
$sel:flags:StreamDescriptorSurfaceCreateInfoGGP :: StreamDescriptorSurfaceCreateInfoGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr StreamDescriptorSurfaceCreateFlagsGGP
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr StreamDescriptorSurfaceCreateFlagsGGP)) (StreamDescriptorSurfaceCreateFlagsGGP
flags)
    Ptr GgpStreamDescriptor -> GgpStreamDescriptor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr GgpStreamDescriptor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor)) (GgpStreamDescriptor
streamDescriptor)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr GgpStreamDescriptor -> GgpStreamDescriptor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr GgpStreamDescriptor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor)) (GgpStreamDescriptor
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct StreamDescriptorSurfaceCreateInfoGGP where
  peekCStruct :: ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> IO StreamDescriptorSurfaceCreateInfoGGP
peekCStruct "pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p = do
    StreamDescriptorSurfaceCreateFlagsGGP
flags <- Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
forall a. Storable a => Ptr a -> IO a
peek @StreamDescriptorSurfaceCreateFlagsGGP (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr StreamDescriptorSurfaceCreateFlagsGGP
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr StreamDescriptorSurfaceCreateFlagsGGP))
    GgpStreamDescriptor
streamDescriptor <- Ptr GgpStreamDescriptor -> IO GgpStreamDescriptor
forall a. Storable a => Ptr a -> IO a
peek @GgpStreamDescriptor (("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP
p ("pCreateInfo" ::: Ptr StreamDescriptorSurfaceCreateInfoGGP)
-> Int -> Ptr GgpStreamDescriptor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr GgpStreamDescriptor))
    StreamDescriptorSurfaceCreateInfoGGP
-> IO StreamDescriptorSurfaceCreateInfoGGP
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StreamDescriptorSurfaceCreateInfoGGP
 -> IO StreamDescriptorSurfaceCreateInfoGGP)
-> StreamDescriptorSurfaceCreateInfoGGP
-> IO StreamDescriptorSurfaceCreateInfoGGP
forall a b. (a -> b) -> a -> b
$ StreamDescriptorSurfaceCreateFlagsGGP
-> GgpStreamDescriptor -> StreamDescriptorSurfaceCreateInfoGGP
StreamDescriptorSurfaceCreateInfoGGP
             StreamDescriptorSurfaceCreateFlagsGGP
flags GgpStreamDescriptor
streamDescriptor

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

instance Zero StreamDescriptorSurfaceCreateInfoGGP where
  zero :: StreamDescriptorSurfaceCreateInfoGGP
zero = StreamDescriptorSurfaceCreateFlagsGGP
-> GgpStreamDescriptor -> StreamDescriptorSurfaceCreateInfoGGP
StreamDescriptorSurfaceCreateInfoGGP
           StreamDescriptorSurfaceCreateFlagsGGP
forall a. Zero a => a
zero
           GgpStreamDescriptor
forall a. Zero a => a
zero


-- | VkStreamDescriptorSurfaceCreateFlagsGGP - Reserved for future use
--
-- = Description
--
-- 'StreamDescriptorSurfaceCreateFlagsGGP' is a bitmask type for setting a
-- mask, but is currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_GGP_stream_descriptor_surface VK_GGP_stream_descriptor_surface>,
-- 'StreamDescriptorSurfaceCreateInfoGGP'
newtype StreamDescriptorSurfaceCreateFlagsGGP = StreamDescriptorSurfaceCreateFlagsGGP Flags
  deriving newtype (StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
(StreamDescriptorSurfaceCreateFlagsGGP
 -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> Eq StreamDescriptorSurfaceCreateFlagsGGP
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c/= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
== :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c== :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
Eq, Eq StreamDescriptorSurfaceCreateFlagsGGP
Eq StreamDescriptorSurfaceCreateFlagsGGP
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> Ord StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
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 :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cmin :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
max :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cmax :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
>= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c>= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
> :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c> :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
<= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c<= :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
< :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$c< :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Bool
compare :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
$ccompare :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> Ordering
$cp1Ord :: Eq StreamDescriptorSurfaceCreateFlagsGGP
Ord, Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
StreamDescriptorSurfaceCreateFlagsGGP -> Int
(StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> (Ptr StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP)
-> (Ptr StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ())
-> (forall b.
    Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP)
-> (forall b.
    Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ())
-> (Ptr StreamDescriptorSurfaceCreateFlagsGGP
    -> IO StreamDescriptorSurfaceCreateFlagsGGP)
-> (Ptr StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ())
-> Storable StreamDescriptorSurfaceCreateFlagsGGP
forall b. Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
forall b.
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> 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 StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpoke :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peek :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeek :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> IO StreamDescriptorSurfaceCreateFlagsGGP
pokeByteOff :: Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peekByteOff :: Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeekByteOff :: forall b. Ptr b -> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
pokeElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
$cpokeElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP -> IO ()
peekElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
$cpeekElemOff :: Ptr StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> IO StreamDescriptorSurfaceCreateFlagsGGP
alignment :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$calignment :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
sizeOf :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$csizeOf :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
Storable, StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
-> Zero StreamDescriptorSurfaceCreateFlagsGGP
forall a. a -> Zero a
zero :: StreamDescriptorSurfaceCreateFlagsGGP
$czero :: StreamDescriptorSurfaceCreateFlagsGGP
Zero, Eq StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
Eq StreamDescriptorSurfaceCreateFlagsGGP
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> StreamDescriptorSurfaceCreateFlagsGGP
-> (Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Bool)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP
    -> Int -> StreamDescriptorSurfaceCreateFlagsGGP)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> Bits StreamDescriptorSurfaceCreateFlagsGGP
Int -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Bool
StreamDescriptorSurfaceCreateFlagsGGP -> Int
StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
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 :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cpopCount :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
rotateR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotateR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
rotateL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotateL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
unsafeShiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cunsafeShiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshiftR :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
unsafeShiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cunsafeShiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshiftL :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
isSigned :: StreamDescriptorSurfaceCreateFlagsGGP -> Bool
$cisSigned :: StreamDescriptorSurfaceCreateFlagsGGP -> Bool
bitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cbitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
bitSizeMaybe :: StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
$cbitSizeMaybe :: StreamDescriptorSurfaceCreateFlagsGGP -> Maybe Int
testBit :: StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
$ctestBit :: StreamDescriptorSurfaceCreateFlagsGGP -> Int -> Bool
complementBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$ccomplementBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
clearBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cclearBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
setBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$csetBit :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
bit :: Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cbit :: Int -> StreamDescriptorSurfaceCreateFlagsGGP
zeroBits :: StreamDescriptorSurfaceCreateFlagsGGP
$czeroBits :: StreamDescriptorSurfaceCreateFlagsGGP
rotate :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$crotate :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
shift :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
$cshift :: StreamDescriptorSurfaceCreateFlagsGGP
-> Int -> StreamDescriptorSurfaceCreateFlagsGGP
complement :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$ccomplement :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
xor :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cxor :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
.|. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$c.|. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
.&. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$c.&. :: StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
-> StreamDescriptorSurfaceCreateFlagsGGP
$cp1Bits :: Eq StreamDescriptorSurfaceCreateFlagsGGP
Bits, Bits StreamDescriptorSurfaceCreateFlagsGGP
Bits StreamDescriptorSurfaceCreateFlagsGGP
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> (StreamDescriptorSurfaceCreateFlagsGGP -> Int)
-> FiniteBits StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$ccountTrailingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
countLeadingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$ccountLeadingZeros :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
finiteBitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cfiniteBitSize :: StreamDescriptorSurfaceCreateFlagsGGP -> Int
$cp1FiniteBits :: Bits StreamDescriptorSurfaceCreateFlagsGGP
FiniteBits)



conNameStreamDescriptorSurfaceCreateFlagsGGP :: String
conNameStreamDescriptorSurfaceCreateFlagsGGP :: String
conNameStreamDescriptorSurfaceCreateFlagsGGP = String
"StreamDescriptorSurfaceCreateFlagsGGP"

enumPrefixStreamDescriptorSurfaceCreateFlagsGGP :: String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP :: String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP = String
""

showTableStreamDescriptorSurfaceCreateFlagsGGP :: [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP :: [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP = []

instance Show StreamDescriptorSurfaceCreateFlagsGGP where
  showsPrec :: Int -> StreamDescriptorSurfaceCreateFlagsGGP -> ShowS
showsPrec = String
-> [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
-> String
-> (StreamDescriptorSurfaceCreateFlagsGGP -> GgpStreamDescriptor)
-> (GgpStreamDescriptor -> ShowS)
-> Int
-> StreamDescriptorSurfaceCreateFlagsGGP
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP
                            [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP
                            String
conNameStreamDescriptorSurfaceCreateFlagsGGP
                            (\(StreamDescriptorSurfaceCreateFlagsGGP GgpStreamDescriptor
x) -> GgpStreamDescriptor
x)
                            (\GgpStreamDescriptor
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GgpStreamDescriptor -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex GgpStreamDescriptor
x)

instance Read StreamDescriptorSurfaceCreateFlagsGGP where
  readPrec :: ReadPrec StreamDescriptorSurfaceCreateFlagsGGP
readPrec = String
-> [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
-> String
-> (GgpStreamDescriptor -> StreamDescriptorSurfaceCreateFlagsGGP)
-> ReadPrec StreamDescriptorSurfaceCreateFlagsGGP
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixStreamDescriptorSurfaceCreateFlagsGGP
                          [(StreamDescriptorSurfaceCreateFlagsGGP, String)]
showTableStreamDescriptorSurfaceCreateFlagsGGP
                          String
conNameStreamDescriptorSurfaceCreateFlagsGGP
                          GgpStreamDescriptor -> StreamDescriptorSurfaceCreateFlagsGGP
StreamDescriptorSurfaceCreateFlagsGGP


type GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION"
pattern GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bGGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: a
$mGGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
GGP_STREAM_DESCRIPTOR_SURFACE_SPEC_VERSION = 1


type GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME = "VK_GGP_stream_descriptor_surface"

-- No documentation found for TopLevel "VK_GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME"
pattern GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bGGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: a
$mGGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
GGP_STREAM_DESCRIPTOR_SURFACE_EXTENSION_NAME = "VK_GGP_stream_descriptor_surface"


type GgpStreamDescriptor = Word32