{-# language CPP #-}
-- No documentation found for Chapter "SemaphoreType"
module Vulkan.Core12.Enums.SemaphoreType  (SemaphoreType( SEMAPHORE_TYPE_BINARY
                                                        , SEMAPHORE_TYPE_TIMELINE
                                                        , ..
                                                        )) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showsPrec)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))

-- | VkSemaphoreType - Specifies the type of a semaphore object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_timeline_semaphore VK_KHR_timeline_semaphore>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_2 VK_VERSION_1_2>,
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.SemaphoreTypeCreateInfo'
newtype SemaphoreType = SemaphoreType Int32
  deriving newtype (SemaphoreType -> SemaphoreType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemaphoreType -> SemaphoreType -> Bool
$c/= :: SemaphoreType -> SemaphoreType -> Bool
== :: SemaphoreType -> SemaphoreType -> Bool
$c== :: SemaphoreType -> SemaphoreType -> Bool
Eq, Eq SemaphoreType
SemaphoreType -> SemaphoreType -> Bool
SemaphoreType -> SemaphoreType -> Ordering
SemaphoreType -> SemaphoreType -> SemaphoreType
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 :: SemaphoreType -> SemaphoreType -> SemaphoreType
$cmin :: SemaphoreType -> SemaphoreType -> SemaphoreType
max :: SemaphoreType -> SemaphoreType -> SemaphoreType
$cmax :: SemaphoreType -> SemaphoreType -> SemaphoreType
>= :: SemaphoreType -> SemaphoreType -> Bool
$c>= :: SemaphoreType -> SemaphoreType -> Bool
> :: SemaphoreType -> SemaphoreType -> Bool
$c> :: SemaphoreType -> SemaphoreType -> Bool
<= :: SemaphoreType -> SemaphoreType -> Bool
$c<= :: SemaphoreType -> SemaphoreType -> Bool
< :: SemaphoreType -> SemaphoreType -> Bool
$c< :: SemaphoreType -> SemaphoreType -> Bool
compare :: SemaphoreType -> SemaphoreType -> Ordering
$ccompare :: SemaphoreType -> SemaphoreType -> Ordering
Ord, Ptr SemaphoreType -> IO SemaphoreType
Ptr SemaphoreType -> Int -> IO SemaphoreType
Ptr SemaphoreType -> Int -> SemaphoreType -> IO ()
Ptr SemaphoreType -> SemaphoreType -> IO ()
SemaphoreType -> Int
forall b. Ptr b -> Int -> IO SemaphoreType
forall b. Ptr b -> Int -> SemaphoreType -> 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 SemaphoreType -> SemaphoreType -> IO ()
$cpoke :: Ptr SemaphoreType -> SemaphoreType -> IO ()
peek :: Ptr SemaphoreType -> IO SemaphoreType
$cpeek :: Ptr SemaphoreType -> IO SemaphoreType
pokeByteOff :: forall b. Ptr b -> Int -> SemaphoreType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SemaphoreType -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreType
pokeElemOff :: Ptr SemaphoreType -> Int -> SemaphoreType -> IO ()
$cpokeElemOff :: Ptr SemaphoreType -> Int -> SemaphoreType -> IO ()
peekElemOff :: Ptr SemaphoreType -> Int -> IO SemaphoreType
$cpeekElemOff :: Ptr SemaphoreType -> Int -> IO SemaphoreType
alignment :: SemaphoreType -> Int
$calignment :: SemaphoreType -> Int
sizeOf :: SemaphoreType -> Int
$csizeOf :: SemaphoreType -> Int
Storable, SemaphoreType
forall a. a -> Zero a
zero :: SemaphoreType
$czero :: SemaphoreType
Zero)

-- | 'SEMAPHORE_TYPE_BINARY' specifies a /binary semaphore/ type that has a
-- boolean payload indicating whether the semaphore is currently signaled
-- or unsignaled. When created, the semaphore is in the unsignaled state.
pattern $bSEMAPHORE_TYPE_BINARY :: SemaphoreType
$mSEMAPHORE_TYPE_BINARY :: forall {r}. SemaphoreType -> ((# #) -> r) -> ((# #) -> r) -> r
SEMAPHORE_TYPE_BINARY = SemaphoreType 0

-- | 'SEMAPHORE_TYPE_TIMELINE' specifies a /timeline semaphore/ type that has
-- a strictly increasing 64-bit unsigned integer payload indicating whether
-- the semaphore is signaled with respect to a particular reference value.
-- When created, the semaphore payload has the value given by the
-- @initialValue@ field of
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.SemaphoreTypeCreateInfo'.
pattern $bSEMAPHORE_TYPE_TIMELINE :: SemaphoreType
$mSEMAPHORE_TYPE_TIMELINE :: forall {r}. SemaphoreType -> ((# #) -> r) -> ((# #) -> r) -> r
SEMAPHORE_TYPE_TIMELINE = SemaphoreType 1

{-# COMPLETE
  SEMAPHORE_TYPE_BINARY
  , SEMAPHORE_TYPE_TIMELINE ::
    SemaphoreType
  #-}

conNameSemaphoreType :: String
conNameSemaphoreType :: String
conNameSemaphoreType = String
"SemaphoreType"

enumPrefixSemaphoreType :: String
enumPrefixSemaphoreType :: String
enumPrefixSemaphoreType = String
"SEMAPHORE_TYPE_"

showTableSemaphoreType :: [(SemaphoreType, String)]
showTableSemaphoreType :: [(SemaphoreType, String)]
showTableSemaphoreType =
  [ (SemaphoreType
SEMAPHORE_TYPE_BINARY, String
"BINARY")
  , (SemaphoreType
SEMAPHORE_TYPE_TIMELINE, String
"TIMELINE")
  ]

instance Show SemaphoreType where
  showsPrec :: Int -> SemaphoreType -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixSemaphoreType
      [(SemaphoreType, String)]
showTableSemaphoreType
      String
conNameSemaphoreType
      (\(SemaphoreType Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read SemaphoreType where
  readPrec :: ReadPrec SemaphoreType
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixSemaphoreType
      [(SemaphoreType, String)]
showTableSemaphoreType
      String
conNameSemaphoreType
      Int32 -> SemaphoreType
SemaphoreType