{-# language CPP #-}
module Vulkan.Core12.Enums.SemaphoreType  (SemaphoreType( SEMAPHORE_TYPE_BINARY
                                                        , SEMAPHORE_TYPE_TIMELINE
                                                        , ..
                                                        )) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Zero (Zero)
-- | VkSemaphoreType - Sepcifies the type of a semaphore object
--
-- = See Also
--
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.SemaphoreTypeCreateInfo'
newtype SemaphoreType = SemaphoreType Int32
  deriving newtype (SemaphoreType -> SemaphoreType -> Bool
(SemaphoreType -> SemaphoreType -> Bool)
-> (SemaphoreType -> SemaphoreType -> Bool) -> Eq SemaphoreType
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
Eq SemaphoreType =>
(SemaphoreType -> SemaphoreType -> Ordering)
-> (SemaphoreType -> SemaphoreType -> Bool)
-> (SemaphoreType -> SemaphoreType -> Bool)
-> (SemaphoreType -> SemaphoreType -> Bool)
-> (SemaphoreType -> SemaphoreType -> Bool)
-> (SemaphoreType -> SemaphoreType -> SemaphoreType)
-> (SemaphoreType -> SemaphoreType -> SemaphoreType)
-> Ord 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
$cp1Ord :: Eq SemaphoreType
Ord, Ptr b -> Int -> IO SemaphoreType
Ptr b -> Int -> SemaphoreType -> IO ()
Ptr SemaphoreType -> IO SemaphoreType
Ptr SemaphoreType -> Int -> IO SemaphoreType
Ptr SemaphoreType -> Int -> SemaphoreType -> IO ()
Ptr SemaphoreType -> SemaphoreType -> IO ()
SemaphoreType -> Int
(SemaphoreType -> Int)
-> (SemaphoreType -> Int)
-> (Ptr SemaphoreType -> Int -> IO SemaphoreType)
-> (Ptr SemaphoreType -> Int -> SemaphoreType -> IO ())
-> (forall b. Ptr b -> Int -> IO SemaphoreType)
-> (forall b. Ptr b -> Int -> SemaphoreType -> IO ())
-> (Ptr SemaphoreType -> IO SemaphoreType)
-> (Ptr SemaphoreType -> SemaphoreType -> IO ())
-> Storable SemaphoreType
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 :: Ptr b -> Int -> SemaphoreType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SemaphoreType -> IO ()
peekByteOff :: 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
SemaphoreType -> Zero 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 -> (Void# -> r) -> (Void# -> r) -> r
SEMAPHORE_TYPE_BINARY = SemaphoreType 0
-- | 'SEMAPHORE_TYPE_TIMELINE' specifies a /timeline semaphore/ type that has
-- a monotonically 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 -> (Void# -> r) -> (Void# -> r) -> r
SEMAPHORE_TYPE_TIMELINE = SemaphoreType 1
{-# complete SEMAPHORE_TYPE_BINARY,
             SEMAPHORE_TYPE_TIMELINE :: SemaphoreType #-}

instance Show SemaphoreType where
  showsPrec :: Int -> SemaphoreType -> ShowS
showsPrec p :: Int
p = \case
    SEMAPHORE_TYPE_BINARY -> String -> ShowS
showString "SEMAPHORE_TYPE_BINARY"
    SEMAPHORE_TYPE_TIMELINE -> String -> ShowS
showString "SEMAPHORE_TYPE_TIMELINE"
    SemaphoreType x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SemaphoreType " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read SemaphoreType where
  readPrec :: ReadPrec SemaphoreType
readPrec = ReadPrec SemaphoreType -> ReadPrec SemaphoreType
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec SemaphoreType)] -> ReadPrec SemaphoreType
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("SEMAPHORE_TYPE_BINARY", SemaphoreType -> ReadPrec SemaphoreType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SemaphoreType
SEMAPHORE_TYPE_BINARY)
                            , ("SEMAPHORE_TYPE_TIMELINE", SemaphoreType -> ReadPrec SemaphoreType
forall (f :: * -> *) a. Applicative f => a -> f a
pure SemaphoreType
SEMAPHORE_TYPE_TIMELINE)]
                     ReadPrec SemaphoreType
-> ReadPrec SemaphoreType -> ReadPrec SemaphoreType
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec SemaphoreType -> ReadPrec SemaphoreType
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "SemaphoreType")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       SemaphoreType -> ReadPrec SemaphoreType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> SemaphoreType
SemaphoreType Int32
v)))