{-# language CPP #-}
-- | = Name
--
-- VK_GGP_frame_token - device extension
--
-- == VK_GGP_frame_token
--
-- [__Name String__]
--     @VK_GGP_frame_token@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     192
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_swapchain@
--
--     -   Requires @VK_GGP_stream_descriptor_surface@
--
-- [__Contact__]
--
--     -   Jean-Francois Roy
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?title=VK_GGP_frame_token:%20&body=@jfroy%20 >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-01-28
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Jean-Francois Roy, Google
--
--     -   Richard O’Grady, Google
--
-- == Description
--
-- This extension allows an application that uses the @VK_KHR_swapchain@
-- extension in combination with a Google Games Platform surface provided
-- by the @VK_GGP_stream_descriptor_surface@ extension to associate a
-- Google Games Platform frame token with a present operation.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Extensions.VK_KHR_swapchain.PresentInfoKHR':
--
--     -   'PresentFrameTokenGGP'
--
-- == New Enum Constants
--
-- -   'GGP_FRAME_TOKEN_EXTENSION_NAME'
--
-- -   'GGP_FRAME_TOKEN_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP'
--
-- == Version History
--
-- -   Revision 1, 2018-11-26 (Jean-Francois Roy)
--
--     -   Initial revision.
--
-- = See Also
--
-- 'PresentFrameTokenGGP'
--
-- = Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_GGP_frame_token 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_frame_token  ( PresentFrameTokenGGP(..)
                                             , GGP_FRAME_TOKEN_SPEC_VERSION
                                             , pattern GGP_FRAME_TOKEN_SPEC_VERSION
                                             , GGP_FRAME_TOKEN_EXTENSION_NAME
                                             , pattern GGP_FRAME_TOKEN_EXTENSION_NAME
                                             , GgpFrameToken
                                             ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
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 (Word32)
import Data.Kind (Type)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP))
-- | VkPresentFrameTokenGGP - The Google Games Platform frame token
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PresentFrameTokenGGP = PresentFrameTokenGGP
  { -- | @frameToken@ is the Google Games Platform frame token.
    --
    -- #VUID-VkPresentFrameTokenGGP-frameToken-02680# @frameToken@ /must/ be a
    -- valid 'GgpFrameToken'
    PresentFrameTokenGGP -> GgpFrameToken
frameToken :: GgpFrameToken }
  deriving (Typeable, PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool
(PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool)
-> (PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool)
-> Eq PresentFrameTokenGGP
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool
$c/= :: PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool
== :: PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool
$c== :: PresentFrameTokenGGP -> PresentFrameTokenGGP -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PresentFrameTokenGGP)
#endif
deriving instance Show PresentFrameTokenGGP

instance ToCStruct PresentFrameTokenGGP where
  withCStruct :: PresentFrameTokenGGP -> (Ptr PresentFrameTokenGGP -> IO b) -> IO b
withCStruct x :: PresentFrameTokenGGP
x f :: Ptr PresentFrameTokenGGP -> IO b
f = Int -> Int -> (Ptr PresentFrameTokenGGP -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PresentFrameTokenGGP -> IO b) -> IO b)
-> (Ptr PresentFrameTokenGGP -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PresentFrameTokenGGP
p -> Ptr PresentFrameTokenGGP -> PresentFrameTokenGGP -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PresentFrameTokenGGP
p PresentFrameTokenGGP
x (Ptr PresentFrameTokenGGP -> IO b
f Ptr PresentFrameTokenGGP
p)
  pokeCStruct :: Ptr PresentFrameTokenGGP -> PresentFrameTokenGGP -> IO b -> IO b
pokeCStruct p :: Ptr PresentFrameTokenGGP
p PresentFrameTokenGGP{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr GgpFrameToken -> GgpFrameToken -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr GgpFrameToken
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GgpFrameToken)) (GgpFrameToken
frameToken)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PresentFrameTokenGGP -> IO b -> IO b
pokeZeroCStruct p :: Ptr PresentFrameTokenGGP
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr GgpFrameToken -> GgpFrameToken -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PresentFrameTokenGGP
p Ptr PresentFrameTokenGGP -> Int -> Ptr GgpFrameToken
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GgpFrameToken)) (GgpFrameToken
forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero PresentFrameTokenGGP where
  zero :: PresentFrameTokenGGP
zero = GgpFrameToken -> PresentFrameTokenGGP
PresentFrameTokenGGP
           GgpFrameToken
forall a. Zero a => a
zero


type GGP_FRAME_TOKEN_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_GGP_FRAME_TOKEN_SPEC_VERSION"
pattern GGP_FRAME_TOKEN_SPEC_VERSION :: forall a . Integral a => a
pattern $bGGP_FRAME_TOKEN_SPEC_VERSION :: a
$mGGP_FRAME_TOKEN_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
GGP_FRAME_TOKEN_SPEC_VERSION = 1


type GGP_FRAME_TOKEN_EXTENSION_NAME = "VK_GGP_frame_token"

-- No documentation found for TopLevel "VK_GGP_FRAME_TOKEN_EXTENSION_NAME"
pattern GGP_FRAME_TOKEN_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bGGP_FRAME_TOKEN_EXTENSION_NAME :: a
$mGGP_FRAME_TOKEN_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
GGP_FRAME_TOKEN_EXTENSION_NAME = "VK_GGP_frame_token"


type GgpFrameToken = Word32