{-# language CPP #-}
module Vulkan.Core11.Enums.ExternalSemaphoreHandleTypeFlagBits  ( ExternalSemaphoreHandleTypeFlagBits( EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT
                                                                                                     , EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT
                                                                                                     , EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT
                                                                                                     , EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT
                                                                                                     , EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT
                                                                                                     , ..
                                                                                                     )
                                                                , ExternalSemaphoreHandleTypeFlags
                                                                ) where

import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
-- | VkExternalSemaphoreHandleTypeFlagBits - Bitmask of valid external
-- semaphore handle types
--
-- = Description
--
-- Note
--
-- Handles of type 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT' generated
-- by the implementation may represent either Linux Sync Files or Android
-- Fences at the implementation’s discretion. Applications /should/ only
-- use operations defined for both types of file descriptors, unless they
-- know via means external to Vulkan the type of the file descriptor, or
-- are prepared to deal with the system-defined operation failures
-- resulting from using the wrong type.
--
-- Some external semaphore handle types can only be shared within the same
-- underlying physical device and\/or the same driver version, as defined
-- in the following table:
--
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | Handle type                                           | 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceIDProperties'::@driverUUID@ | 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceIDProperties'::@deviceUUID@ |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT'        | Must match                                                                                                 | Must match                                                                                                 |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT'     | Must match                                                                                                 | Must match                                                                                                 |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT' | Must match                                                                                                 | Must match                                                                                                 |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT'      | Must match                                                                                                 | Must match                                                                                                 |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT'          | No restriction                                                                                             | No restriction                                                                                             |
-- +-------------------------------------------------------+------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------+
--
-- External semaphore handle types compatibility
--
-- = See Also
--
-- 'ExternalSemaphoreHandleTypeFlags',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.ImportSemaphoreFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.ImportSemaphoreWin32HandleInfoKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_external_semaphore_capabilities.PhysicalDeviceExternalSemaphoreInfo',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.SemaphoreGetFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.SemaphoreGetWin32HandleInfoKHR'
newtype ExternalSemaphoreHandleTypeFlagBits = ExternalSemaphoreHandleTypeFlagBits Flags
  deriving newtype (ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
(ExternalSemaphoreHandleTypeFlagBits
 -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> Eq ExternalSemaphoreHandleTypeFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c/= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
== :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c== :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
Eq, Eq ExternalSemaphoreHandleTypeFlagBits
Eq ExternalSemaphoreHandleTypeFlagBits =>
(ExternalSemaphoreHandleTypeFlagBits
 -> ExternalSemaphoreHandleTypeFlagBits -> Ordering)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits)
-> Ord ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Ordering
ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
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 :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$cmin :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
max :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$cmax :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
>= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c>= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
> :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c> :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
<= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c<= :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
< :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
$c< :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Bool
compare :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Ordering
$ccompare :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> Ordering
$cp1Ord :: Eq ExternalSemaphoreHandleTypeFlagBits
Ord, Ptr b -> Int -> IO ExternalSemaphoreHandleTypeFlagBits
Ptr b -> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
Ptr ExternalSemaphoreHandleTypeFlagBits
-> IO ExternalSemaphoreHandleTypeFlagBits
Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> IO ExternalSemaphoreHandleTypeFlagBits
Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
Ptr ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> IO ()
ExternalSemaphoreHandleTypeFlagBits -> Int
(ExternalSemaphoreHandleTypeFlagBits -> Int)
-> (ExternalSemaphoreHandleTypeFlagBits -> Int)
-> (Ptr ExternalSemaphoreHandleTypeFlagBits
    -> Int -> IO ExternalSemaphoreHandleTypeFlagBits)
-> (Ptr ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ())
-> (forall b.
    Ptr b -> Int -> IO ExternalSemaphoreHandleTypeFlagBits)
-> (forall b.
    Ptr b -> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ())
-> (Ptr ExternalSemaphoreHandleTypeFlagBits
    -> IO ExternalSemaphoreHandleTypeFlagBits)
-> (Ptr ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits -> IO ())
-> Storable ExternalSemaphoreHandleTypeFlagBits
forall b. Ptr b -> Int -> IO ExternalSemaphoreHandleTypeFlagBits
forall b.
Ptr b -> Int -> ExternalSemaphoreHandleTypeFlagBits -> 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 ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> IO ()
$cpoke :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits -> IO ()
peek :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> IO ExternalSemaphoreHandleTypeFlagBits
$cpeek :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> IO ExternalSemaphoreHandleTypeFlagBits
pokeByteOff :: Ptr b -> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO ExternalSemaphoreHandleTypeFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ExternalSemaphoreHandleTypeFlagBits
pokeElemOff :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
$cpokeElemOff :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits -> IO ()
peekElemOff :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> IO ExternalSemaphoreHandleTypeFlagBits
$cpeekElemOff :: Ptr ExternalSemaphoreHandleTypeFlagBits
-> Int -> IO ExternalSemaphoreHandleTypeFlagBits
alignment :: ExternalSemaphoreHandleTypeFlagBits -> Int
$calignment :: ExternalSemaphoreHandleTypeFlagBits -> Int
sizeOf :: ExternalSemaphoreHandleTypeFlagBits -> Int
$csizeOf :: ExternalSemaphoreHandleTypeFlagBits -> Int
Storable, ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits
-> Zero ExternalSemaphoreHandleTypeFlagBits
forall a. a -> Zero a
zero :: ExternalSemaphoreHandleTypeFlagBits
$czero :: ExternalSemaphoreHandleTypeFlagBits
Zero, Eq ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits
Eq ExternalSemaphoreHandleTypeFlagBits =>
(ExternalSemaphoreHandleTypeFlagBits
 -> ExternalSemaphoreHandleTypeFlagBits
 -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> ExternalSemaphoreHandleTypeFlagBits
-> (Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits -> Int -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits -> Maybe Int)
-> (ExternalSemaphoreHandleTypeFlagBits -> Int)
-> (ExternalSemaphoreHandleTypeFlagBits -> Bool)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits
    -> Int -> ExternalSemaphoreHandleTypeFlagBits)
-> (ExternalSemaphoreHandleTypeFlagBits -> Int)
-> Bits ExternalSemaphoreHandleTypeFlagBits
Int -> ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits -> Bool
ExternalSemaphoreHandleTypeFlagBits -> Int
ExternalSemaphoreHandleTypeFlagBits -> Maybe Int
ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits -> Int -> Bool
ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
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 :: ExternalSemaphoreHandleTypeFlagBits -> Int
$cpopCount :: ExternalSemaphoreHandleTypeFlagBits -> Int
rotateR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$crotateR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
rotateL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$crotateL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
unsafeShiftR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cunsafeShiftR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
shiftR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cshiftR :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
unsafeShiftL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cunsafeShiftL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
shiftL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cshiftL :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
isSigned :: ExternalSemaphoreHandleTypeFlagBits -> Bool
$cisSigned :: ExternalSemaphoreHandleTypeFlagBits -> Bool
bitSize :: ExternalSemaphoreHandleTypeFlagBits -> Int
$cbitSize :: ExternalSemaphoreHandleTypeFlagBits -> Int
bitSizeMaybe :: ExternalSemaphoreHandleTypeFlagBits -> Maybe Int
$cbitSizeMaybe :: ExternalSemaphoreHandleTypeFlagBits -> Maybe Int
testBit :: ExternalSemaphoreHandleTypeFlagBits -> Int -> Bool
$ctestBit :: ExternalSemaphoreHandleTypeFlagBits -> Int -> Bool
complementBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$ccomplementBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
clearBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cclearBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
setBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$csetBit :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
bit :: Int -> ExternalSemaphoreHandleTypeFlagBits
$cbit :: Int -> ExternalSemaphoreHandleTypeFlagBits
zeroBits :: ExternalSemaphoreHandleTypeFlagBits
$czeroBits :: ExternalSemaphoreHandleTypeFlagBits
rotate :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$crotate :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
shift :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
$cshift :: ExternalSemaphoreHandleTypeFlagBits
-> Int -> ExternalSemaphoreHandleTypeFlagBits
complement :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$ccomplement :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
xor :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$cxor :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
.|. :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$c.|. :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
.&. :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$c.&. :: ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
-> ExternalSemaphoreHandleTypeFlagBits
$cp1Bits :: Eq ExternalSemaphoreHandleTypeFlagBits
Bits)

-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT' specifies a POSIX file
-- descriptor handle that has only limited valid usage outside of Vulkan
-- and other compatible APIs. It /must/ be compatible with the POSIX system
-- calls @dup@, @dup2@, @close@, and the non-standard system call @dup3@.
-- Additionally, it /must/ be transportable over a socket using an
-- @SCM_RIGHTS@ control message. It owns a reference to the underlying
-- synchronization primitive represented by its Vulkan semaphore object.
pattern $bEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT :: ExternalSemaphoreHandleTypeFlagBits
$mEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT :: forall r.
ExternalSemaphoreHandleTypeFlagBits
-> (Void# -> r) -> (Void# -> r) -> r
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT = ExternalSemaphoreHandleTypeFlagBits 0x00000001
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT' specifies an NT handle
-- that has only limited valid usage outside of Vulkan and other compatible
-- APIs. It /must/ be compatible with the functions @DuplicateHandle@,
-- @CloseHandle@, @CompareObjectHandles@, @GetHandleInformation@, and
-- @SetHandleInformation@. It owns a reference to the underlying
-- synchronization primitive represented by its Vulkan semaphore object.
pattern $bEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT :: ExternalSemaphoreHandleTypeFlagBits
$mEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT :: forall r.
ExternalSemaphoreHandleTypeFlagBits
-> (Void# -> r) -> (Void# -> r) -> r
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT = ExternalSemaphoreHandleTypeFlagBits 0x00000002
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT' specifies a global
-- share handle that has only limited valid usage outside of Vulkan and
-- other compatible APIs. It is not compatible with any native APIs. It
-- does not own a reference to the underlying synchronization primitive
-- represented its Vulkan semaphore object, and will therefore become
-- invalid when all Vulkan semaphore objects associated with it are
-- destroyed.
pattern $bEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT :: ExternalSemaphoreHandleTypeFlagBits
$mEXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT :: forall r.
ExternalSemaphoreHandleTypeFlagBits
-> (Void# -> r) -> (Void# -> r) -> r
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT = ExternalSemaphoreHandleTypeFlagBits 0x00000004
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT' specifies an NT handle
-- returned by @ID3D12Device@::@CreateSharedHandle@ referring to a Direct3D
-- 12 fence, or @ID3D11Device5@::'Vulkan.Core10.Fence.createFence' by a
-- Direct3D 11 fence. It owns a reference to the underlying synchronization
-- primitive associated with the Direct3D fence.
pattern $bEXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT :: ExternalSemaphoreHandleTypeFlagBits
$mEXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT :: forall r.
ExternalSemaphoreHandleTypeFlagBits
-> (Void# -> r) -> (Void# -> r) -> r
EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT = ExternalSemaphoreHandleTypeFlagBits 0x00000008
-- | 'EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT' specifies a POSIX file
-- descriptor handle to a Linux Sync File or Android Fence object. It can
-- be used with any native API accepting a valid sync file or fence as
-- input. It owns a reference to the underlying synchronization primitive
-- associated with the file descriptor. Implementations which support
-- importing this handle type /must/ accept any type of sync or fence FD
-- supported by the native system they are running on.
pattern $bEXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT :: ExternalSemaphoreHandleTypeFlagBits
$mEXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT :: forall r.
ExternalSemaphoreHandleTypeFlagBits
-> (Void# -> r) -> (Void# -> r) -> r
EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT = ExternalSemaphoreHandleTypeFlagBits 0x00000010

type ExternalSemaphoreHandleTypeFlags = ExternalSemaphoreHandleTypeFlagBits

instance Show ExternalSemaphoreHandleTypeFlagBits where
  showsPrec :: Int -> ExternalSemaphoreHandleTypeFlagBits -> ShowS
showsPrec p :: Int
p = \case
    EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT -> String -> ShowS
showString "EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT"
    EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT -> String -> ShowS
showString "EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT"
    EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT -> String -> ShowS
showString "EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT"
    EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT -> String -> ShowS
showString "EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT"
    EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT -> String -> ShowS
showString "EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT"
    ExternalSemaphoreHandleTypeFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ExternalSemaphoreHandleTypeFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read ExternalSemaphoreHandleTypeFlagBits where
  readPrec :: ReadPrec ExternalSemaphoreHandleTypeFlagBits
readPrec = ReadPrec ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ExternalSemaphoreHandleTypeFlagBits)]
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT", ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExternalSemaphoreHandleTypeFlagBits
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_FD_BIT)
                            , ("EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT", ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExternalSemaphoreHandleTypeFlagBits
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_BIT)
                            , ("EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT", ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExternalSemaphoreHandleTypeFlagBits
EXTERNAL_SEMAPHORE_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT)
                            , ("EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT", ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExternalSemaphoreHandleTypeFlagBits
EXTERNAL_SEMAPHORE_HANDLE_TYPE_D3D12_FENCE_BIT)
                            , ("EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT", ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure ExternalSemaphoreHandleTypeFlagBits
EXTERNAL_SEMAPHORE_HANDLE_TYPE_SYNC_FD_BIT)]
                     ReadPrec ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "ExternalSemaphoreHandleTypeFlagBits")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       ExternalSemaphoreHandleTypeFlagBits
-> ReadPrec ExternalSemaphoreHandleTypeFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> ExternalSemaphoreHandleTypeFlagBits
ExternalSemaphoreHandleTypeFlagBits Flags
v)))