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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PatternSynonyms       #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE UndecidableInstances  #-}
module Graphics.Vulkan.Types.Struct.DebugUtilsLabelEXT
       (VkDebugUtilsLabelEXT(..)) where
import           Foreign.Storable                         (Storable (..))
import           GHC.Base                                 (Addr#, ByteArray#,
                                                           Proxy#,
                                                           byteArrayContents#,
                                                           plusAddr#, proxy#)
import           GHC.TypeLits                             (KnownNat, natVal') -- ' closing tick for hsc2hs
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkDebugUtilsLabelEXT {
--   >     VkStructureType sType;
--   >     const void*                            pNext;
--   >     const char*      pLabelName;
--   >     float                  color[4];
--   > } VkDebugUtilsLabelEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkDebugUtilsLabelEXT VkDebugUtilsLabelEXT registry at www.khronos.org>
data VkDebugUtilsLabelEXT = VkDebugUtilsLabelEXT# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkDebugUtilsLabelEXT where
        sizeOf ~_ = (40)
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "pLabelName" VkDebugUtilsLabelEXT where
        type FieldType "pLabelName" VkDebugUtilsLabelEXT = CString
        type FieldOptional "pLabelName" VkDebugUtilsLabelEXT = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pLabelName" VkDebugUtilsLabelEXT =
             (16)
{-# LINE 150 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
        type FieldIsArray "pLabelName" VkDebugUtilsLabelEXT = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "pLabelName" VkDebugUtilsLabelEXT where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "pLabelName" VkDebugUtilsLabelEXT where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

instance {-# OVERLAPPING #-} HasField "color" VkDebugUtilsLabelEXT
         where
        type FieldType "color" VkDebugUtilsLabelEXT =
             Float
{-# LINE 180 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
        type FieldOptional "color" VkDebugUtilsLabelEXT = 'True -- ' closing tick for hsc2hs
        type FieldOffset "color" VkDebugUtilsLabelEXT =
             (24)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
        type FieldIsArray "color" VkDebugUtilsLabelEXT = 'True -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         (KnownNat idx, IndexInBounds "color" idx VkDebugUtilsLabelEXT) =>
         CanReadFieldArray "color" idx VkDebugUtilsLabelEXT
         where
        {-# SPECIALISE instance
                       CanReadFieldArray "color" 0 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "color" 1 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "color" 2 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanReadFieldArray "color" 3 VkDebugUtilsLabelEXT #-}
        type FieldArrayLength "color" VkDebugUtilsLabelEXT = 4

        {-# INLINE fieldArrayLength #-}
        fieldArrayLength = 4

        {-# INLINE getFieldArray #-}
        getFieldArray = f
          where {-# NOINLINE f #-}
                f x = unsafeDupablePerformIO (peekByteOff (unsafePtr x) off)
                off
                  = (24) +
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                      sizeOf (undefined :: Float) *
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                        fromInteger (natVal' (proxy# :: Proxy# idx)) -- ' closing tick for hsc2hs

        {-# INLINE readFieldArray #-}
        readFieldArray p
          = peekByteOff p
              ((24) +
{-# LINE 224 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                 sizeOf (undefined :: Float) *
{-# LINE 225 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                   fromInteger (natVal' (proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         (KnownNat idx, IndexInBounds "color" idx VkDebugUtilsLabelEXT) =>
         CanWriteFieldArray "color" idx VkDebugUtilsLabelEXT
         where
        {-# SPECIALISE instance
                       CanWriteFieldArray "color" 0 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "color" 1 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "color" 2 VkDebugUtilsLabelEXT #-}

        {-# SPECIALISE instance
                       CanWriteFieldArray "color" 3 VkDebugUtilsLabelEXT #-}

        {-# INLINE writeFieldArray #-}
        writeFieldArray p
          = pokeByteOff p
              ((24) +
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                 sizeOf (undefined :: Float) *
{-# LINE 248 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                   fromInteger (natVal' (proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance Show VkDebugUtilsLabelEXT where
        showsPrec d x
          = showString "VkDebugUtilsLabelEXT {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "pLabelName = " .
                            showsPrec d (getField @"pLabelName" x) .
                              showString ", " .
                                (showString "color = [" .
                                   showsPrec d
                                     (let s = sizeOf
                                                (undefined ::
                                                   FieldType "color" VkDebugUtilsLabelEXT)
                                          o = fieldOffset @"color" @VkDebugUtilsLabelEXT
                                          f i
                                            = peekByteOff (unsafePtr x) i ::
                                                IO (FieldType "color" VkDebugUtilsLabelEXT)
                                        in
                                        unsafeDupablePerformIO . mapM f $
                                          map (\ i -> o + i * s) [0 .. 4 - 1])
                                     . showChar ']')
                                  . showChar '}'