{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_surface_protected_capabilities  ( SurfaceProtectedCapabilitiesKHR(..)
                                                                , KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION
                                                                , pattern KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION
                                                                , KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME
                                                                , pattern KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME
                                                                ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_PROTECTED_CAPABILITIES_KHR))
-- | VkSurfaceProtectedCapabilitiesKHR - Structure describing capability of a
-- surface to be protected
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SurfaceProtectedCapabilitiesKHR = SurfaceProtectedCapabilitiesKHR
  { -- | @supportsProtected@ specifies whether a protected swapchain created from
    -- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'::@surface@
    -- for a particular windowing system /can/ be displayed on screen or not.
    -- If @supportsProtected@ is 'Vulkan.Core10.FundamentalTypes.TRUE', then
    -- creation of swapchains with the
    -- 'Vulkan.Extensions.VK_KHR_swapchain.SWAPCHAIN_CREATE_PROTECTED_BIT_KHR'
    -- flag set /must/ be supported for @surface@.
    SurfaceProtectedCapabilitiesKHR -> Bool
supportsProtected :: Bool }
  deriving (Typeable, SurfaceProtectedCapabilitiesKHR
-> SurfaceProtectedCapabilitiesKHR -> Bool
(SurfaceProtectedCapabilitiesKHR
 -> SurfaceProtectedCapabilitiesKHR -> Bool)
-> (SurfaceProtectedCapabilitiesKHR
    -> SurfaceProtectedCapabilitiesKHR -> Bool)
-> Eq SurfaceProtectedCapabilitiesKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceProtectedCapabilitiesKHR
-> SurfaceProtectedCapabilitiesKHR -> Bool
$c/= :: SurfaceProtectedCapabilitiesKHR
-> SurfaceProtectedCapabilitiesKHR -> Bool
== :: SurfaceProtectedCapabilitiesKHR
-> SurfaceProtectedCapabilitiesKHR -> Bool
$c== :: SurfaceProtectedCapabilitiesKHR
-> SurfaceProtectedCapabilitiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceProtectedCapabilitiesKHR)
#endif
deriving instance Show SurfaceProtectedCapabilitiesKHR

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

instance FromCStruct SurfaceProtectedCapabilitiesKHR where
  peekCStruct :: Ptr SurfaceProtectedCapabilitiesKHR
-> IO SurfaceProtectedCapabilitiesKHR
peekCStruct p :: Ptr SurfaceProtectedCapabilitiesKHR
p = do
    Bool32
supportsProtected <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SurfaceProtectedCapabilitiesKHR
p Ptr SurfaceProtectedCapabilitiesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    SurfaceProtectedCapabilitiesKHR
-> IO SurfaceProtectedCapabilitiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceProtectedCapabilitiesKHR
 -> IO SurfaceProtectedCapabilitiesKHR)
-> SurfaceProtectedCapabilitiesKHR
-> IO SurfaceProtectedCapabilitiesKHR
forall a b. (a -> b) -> a -> b
$ Bool -> SurfaceProtectedCapabilitiesKHR
SurfaceProtectedCapabilitiesKHR
             (Bool32 -> Bool
bool32ToBool Bool32
supportsProtected)

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

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


type KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION"
pattern KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION :: a
$mKHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_SURFACE_PROTECTED_CAPABILITIES_SPEC_VERSION = 1


type KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME = "VK_KHR_surface_protected_capabilities"

-- No documentation found for TopLevel "VK_KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME"
pattern KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME :: a
$mKHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_SURFACE_PROTECTED_CAPABILITIES_EXTENSION_NAME = "VK_KHR_surface_protected_capabilities"