{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

{-# LINE 2 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Semaphore
       (VkSemaphoreCreateInfo(..), VkSemaphoreGetFdInfoKHR(..)) where
import           Foreign.Storable                         (Storable (..))
import           GHC.Base                                 (Addr#, ByteArray#,
                                                           byteArrayContents#,
                                                           plusAddr#)
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           Graphics.Vulkan.Types.Bitmasks           (VkSemaphoreCreateFlags)
import           Graphics.Vulkan.Types.Enum.External      (VkExternalSemaphoreHandleTypeFlagBits)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Handles            (VkSemaphore)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkSemaphoreCreateInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkSemaphoreCreateFlags flags;
--   > } VkSemaphoreCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSemaphoreCreateInfo VkSemaphoreCreateInfo registry at www.khronos.org>
data VkSemaphoreCreateInfo = VkSemaphoreCreateInfo# Addr#
                                                    ByteArray#

instance Eq VkSemaphoreCreateInfo where
        (VkSemaphoreCreateInfo# a _) == x@(VkSemaphoreCreateInfo# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkSemaphoreCreateInfo where
        (VkSemaphoreCreateInfo# a _) `compare`
          x@(VkSemaphoreCreateInfo# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkSemaphoreCreateInfo where
        sizeOf ~_ = (24)
{-# LINE 48 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (8)
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkSemaphoreCreateInfo where
        unsafeAddr (VkSemaphoreCreateInfo# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkSemaphoreCreateInfo# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkSemaphoreCreateInfo# (plusAddr# (byteArrayContents# b) off) b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkSemaphoreCreateInfo where
        type StructFields VkSemaphoreCreateInfo =
             '["sType", "pNext", "flags"] -- ' closing tick for hsc2hs
        type CUnionType VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkSemaphoreCreateInfo = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "sType" VkSemaphoreCreateInfo
         where
        type FieldType "sType" VkSemaphoreCreateInfo = VkStructureType
        type FieldOptional "sType" VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkSemaphoreCreateInfo =
             (0)
{-# LINE 85 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "sType" VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (0)
{-# LINE 92 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkSemaphoreCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-} HasField "pNext" VkSemaphoreCreateInfo
         where
        type FieldType "pNext" VkSemaphoreCreateInfo = Ptr Void
        type FieldOptional "pNext" VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkSemaphoreCreateInfo =
             (8)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "pNext" VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (8)
{-# LINE 123 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkSemaphoreCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 130 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-} HasField "flags" VkSemaphoreCreateInfo
         where
        type FieldType "flags" VkSemaphoreCreateInfo =
             VkSemaphoreCreateFlags
        type FieldOptional "flags" VkSemaphoreCreateInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkSemaphoreCreateInfo =
             (16)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "flags" VkSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset = (16)
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkSemaphoreCreateInfo where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 162 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 166 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 172 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance Show VkSemaphoreCreateInfo where
        showsPrec d x
          = showString "VkSemaphoreCreateInfo {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "flags = " .
                            showsPrec d (getField @"flags" x) . showChar '}'

-- | > typedef struct VkSemaphoreGetFdInfoKHR {
--   >     VkStructureType sType;
--   >     const void*                      pNext;
--   >     VkSemaphore                      semaphore;
--   >     VkExternalSemaphoreHandleTypeFlagBits handleType;
--   > } VkSemaphoreGetFdInfoKHR;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSemaphoreGetFdInfoKHR VkSemaphoreGetFdInfoKHR registry at www.khronos.org>
data VkSemaphoreGetFdInfoKHR = VkSemaphoreGetFdInfoKHR# Addr#
                                                        ByteArray#

instance Eq VkSemaphoreGetFdInfoKHR where
        (VkSemaphoreGetFdInfoKHR# a _) == x@(VkSemaphoreGetFdInfoKHR# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkSemaphoreGetFdInfoKHR where
        (VkSemaphoreGetFdInfoKHR# a _) `compare`
          x@(VkSemaphoreGetFdInfoKHR# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkSemaphoreGetFdInfoKHR where
        sizeOf ~_ = (32)
{-# LINE 210 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (8)
{-# LINE 213 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkSemaphoreGetFdInfoKHR where
        unsafeAddr (VkSemaphoreGetFdInfoKHR# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkSemaphoreGetFdInfoKHR# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkSemaphoreGetFdInfoKHR# (plusAddr# (byteArrayContents# b) off) b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkSemaphoreGetFdInfoKHR where
        type StructFields VkSemaphoreGetFdInfoKHR =
             '["sType", "pNext", "semaphore", "handleType"] -- ' closing tick for hsc2hs
        type CUnionType VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type StructExtends VkSemaphoreGetFdInfoKHR = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkSemaphoreGetFdInfoKHR where
        type FieldType "sType" VkSemaphoreGetFdInfoKHR = VkStructureType
        type FieldOptional "sType" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkSemaphoreGetFdInfoKHR =
             (0)
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "sType" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (0)
{-# LINE 254 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkSemaphoreGetFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 261 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 265 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkSemaphoreGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 271 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkSemaphoreGetFdInfoKHR where
        type FieldType "pNext" VkSemaphoreGetFdInfoKHR = Ptr Void
        type FieldOptional "pNext" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkSemaphoreGetFdInfoKHR =
             (8)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "pNext" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (8)
{-# LINE 285 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkSemaphoreGetFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 292 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 296 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkSemaphoreGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 302 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "semaphore" VkSemaphoreGetFdInfoKHR where
        type FieldType "semaphore" VkSemaphoreGetFdInfoKHR = VkSemaphore
        type FieldOptional "semaphore" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "semaphore" VkSemaphoreGetFdInfoKHR =
             (16)
{-# LINE 309 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "semaphore" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (16)
{-# LINE 317 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "semaphore" VkSemaphoreGetFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 324 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 328 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "semaphore" VkSemaphoreGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 334 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleType" VkSemaphoreGetFdInfoKHR where
        type FieldType "handleType" VkSemaphoreGetFdInfoKHR =
             VkExternalSemaphoreHandleTypeFlagBits
        type FieldOptional "handleType" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "handleType" VkSemaphoreGetFdInfoKHR =
             (24)
{-# LINE 342 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
        type FieldIsArray "handleType" VkSemaphoreGetFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 350 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkSemaphoreGetFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 357 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 361 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkSemaphoreGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 367 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}

instance Show VkSemaphoreGetFdInfoKHR where
        showsPrec d x
          = showString "VkSemaphoreGetFdInfoKHR {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "semaphore = " .
                            showsPrec d (getField @"semaphore" x) .
                              showString ", " .
                                showString "handleType = " .
                                  showsPrec d (getField @"handleType" x) . showChar '}'