{-# LINE 1 "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# Addr#
a ByteArray#
_) == :: VkDebugUtilsLabelEXT -> VkDebugUtilsLabelEXT -> Bool
== x :: VkDebugUtilsLabelEXT
x@(VkDebugUtilsLabelEXT# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDebugUtilsLabelEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkDebugUtilsLabelEXT
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

instance Ord VkDebugUtilsLabelEXT where
        (VkDebugUtilsLabelEXT# Addr#
a ByteArray#
_) compare :: VkDebugUtilsLabelEXT -> VkDebugUtilsLabelEXT -> Ordering
`compare` x :: VkDebugUtilsLabelEXT
x@(VkDebugUtilsLabelEXT# Addr#
b ByteArray#
_)
          = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDebugUtilsLabelEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkDebugUtilsLabelEXT
x) Addr#
a Addr#
b

        {-# INLINE compare #-}

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

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

        {-# INLINE alignment #-}
        peek :: Ptr VkDebugUtilsLabelEXT -> IO VkDebugUtilsLabelEXT
peek = Ptr VkDebugUtilsLabelEXT -> IO VkDebugUtilsLabelEXT
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#

        {-# INLINE peek #-}
        poke :: Ptr VkDebugUtilsLabelEXT -> VkDebugUtilsLabelEXT -> IO ()
poke = Ptr VkDebugUtilsLabelEXT -> VkDebugUtilsLabelEXT -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkDebugUtilsLabelEXT where
        unsafeAddr :: VkDebugUtilsLabelEXT -> Addr#
unsafeAddr (VkDebugUtilsLabelEXT# Addr#
a ByteArray#
_) = Addr#
a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray :: VkDebugUtilsLabelEXT -> ByteArray#
unsafeByteArray (VkDebugUtilsLabelEXT# Addr#
_ ByteArray#
b) = ByteArray#
b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkDebugUtilsLabelEXT
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkDebugUtilsLabelEXT
VkDebugUtilsLabelEXT# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkDebugUtilsLabelEXT where
        {-# NOINLINE getField #-}
        getField :: VkDebugUtilsLabelEXT -> FieldType "sType" VkDebugUtilsLabelEXT
getField VkDebugUtilsLabelEXT
x
          = IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkDebugUtilsLabelEXT -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDebugUtilsLabelEXT -> Ptr VkDebugUtilsLabelEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDebugUtilsLabelEXT
x) (Int
0))
{-# LINE 102 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkDebugUtilsLabelEXT
-> IO (FieldType "sType" VkDebugUtilsLabelEXT)
readField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDebugUtilsLabelEXT
p (Int
0)
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkDebugUtilsLabelEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkDebugUtilsLabelEXT
-> FieldType "sType" VkDebugUtilsLabelEXT -> IO ()
writeField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDebugUtilsLabelEXT
p (Int
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkDebugUtilsLabelEXT where
        {-# NOINLINE getField #-}
        getField :: VkDebugUtilsLabelEXT -> FieldType "pNext" VkDebugUtilsLabelEXT
getField VkDebugUtilsLabelEXT
x
          = IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkDebugUtilsLabelEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDebugUtilsLabelEXT -> Ptr VkDebugUtilsLabelEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDebugUtilsLabelEXT
x) (Int
8))
{-# LINE 133 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkDebugUtilsLabelEXT
-> IO (FieldType "pNext" VkDebugUtilsLabelEXT)
readField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDebugUtilsLabelEXT
p (Int
8)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkDebugUtilsLabelEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkDebugUtilsLabelEXT
-> FieldType "pNext" VkDebugUtilsLabelEXT -> IO ()
writeField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDebugUtilsLabelEXT
p (Int
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "pLabelName" VkDebugUtilsLabelEXT where
        {-# NOINLINE getField #-}
        getField :: VkDebugUtilsLabelEXT -> FieldType "pLabelName" VkDebugUtilsLabelEXT
getField VkDebugUtilsLabelEXT
x
          = IO CString -> CString
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkDebugUtilsLabelEXT -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDebugUtilsLabelEXT -> Ptr VkDebugUtilsLabelEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDebugUtilsLabelEXT
x) (Int
16))
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkDebugUtilsLabelEXT
-> IO (FieldType "pLabelName" VkDebugUtilsLabelEXT)
readField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDebugUtilsLabelEXT
p (Int
16)
{-# LINE 169 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pLabelName" VkDebugUtilsLabelEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkDebugUtilsLabelEXT
-> FieldType "pLabelName" VkDebugUtilsLabelEXT -> IO ()
writeField Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDebugUtilsLabelEXT
p (Int
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 :: Bool
fieldOptional = Bool
True

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
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 :: Int
fieldArrayLength = Int
4

        {-# INLINE getFieldArray #-}
        getFieldArray :: VkDebugUtilsLabelEXT -> FieldType "color" VkDebugUtilsLabelEXT
getFieldArray = VkDebugUtilsLabelEXT -> Float
VkDebugUtilsLabelEXT -> FieldType "color" VkDebugUtilsLabelEXT
f
          where {-# NOINLINE f #-}
                f :: VkDebugUtilsLabelEXT -> Float
f VkDebugUtilsLabelEXT
x = IO Float -> Float
forall a. IO a -> a
unsafeDupablePerformIO (Ptr VkDebugUtilsLabelEXT -> Int -> IO Float
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDebugUtilsLabelEXT -> Ptr VkDebugUtilsLabelEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDebugUtilsLabelEXT
x) Int
off)
                off :: Int
off
                  = (Int
24) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                      Float -> Int
forall a. Storable a => a -> Int
sizeOf (Float
forall a. HasCallStack => a
undefined :: Float) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                        Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx)) -- ' closing tick for hsc2hs

        {-# INLINE readFieldArray #-}
        readFieldArray :: Ptr VkDebugUtilsLabelEXT
-> IO (FieldType "color" VkDebugUtilsLabelEXT)
readFieldArray Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> IO Float
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDebugUtilsLabelEXT
p
              ((Int
24) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 224 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                 Float -> Int
forall a. Storable a => a -> Int
sizeOf (Float
forall a. HasCallStack => a
undefined :: Float) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
{-# LINE 225 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
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 :: Ptr VkDebugUtilsLabelEXT
-> FieldType "color" VkDebugUtilsLabelEXT -> IO ()
writeFieldArray Ptr VkDebugUtilsLabelEXT
p
          = Ptr VkDebugUtilsLabelEXT -> Int -> Float -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDebugUtilsLabelEXT
p
              ((Int
24) Int -> Int -> Int
forall a. Num a => a -> a -> a
+
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                 Float -> Int
forall a. Storable a => a -> Int
sizeOf (Float
forall a. HasCallStack => a
undefined :: Float) Int -> Int -> Int
forall a. Num a => a -> a -> a
*
{-# LINE 248 "src-gen/Graphics/Vulkan/Types/Struct/DebugUtilsLabelEXT.hsc" #-}
                   Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Proxy# idx -> Integer
forall (n :: Nat). KnownNat n => Proxy# n -> Integer
natVal' (Proxy# idx
forall k (a :: k). Proxy# a
proxy# :: Proxy# idx))) -- ' closing tick for hsc2hs

instance Show VkDebugUtilsLabelEXT where
        showsPrec :: Int -> VkDebugUtilsLabelEXT -> ShowS
showsPrec Int
d VkDebugUtilsLabelEXT
x
          = String -> ShowS
showString String
"VkDebugUtilsLabelEXT {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"sType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkStructureType -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkDebugUtilsLabelEXT -> FieldType "sType" VkDebugUtilsLabelEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkDebugUtilsLabelEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    String -> ShowS
showString String
"pNext = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Ptr Void -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkDebugUtilsLabelEXT -> FieldType "pNext" VkDebugUtilsLabelEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkDebugUtilsLabelEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                          String -> ShowS
showString String
"pLabelName = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> CString -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkDebugUtilsLabelEXT -> FieldType "pLabelName" VkDebugUtilsLabelEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pLabelName" VkDebugUtilsLabelEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                (String -> ShowS
showString String
"color = [" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                   Int -> [Float] -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
                                     (let s :: Int
s = Float -> Int
forall a. Storable a => a -> Int
sizeOf
                                                (FieldType "color" VkDebugUtilsLabelEXT
forall a. HasCallStack => a
undefined ::
                                                   FieldType "color" VkDebugUtilsLabelEXT)
                                          o :: Int
o = HasField "color" VkDebugUtilsLabelEXT => Int
forall (fname :: Symbol) a. HasField fname a => Int
fieldOffset @"color" @VkDebugUtilsLabelEXT
                                          f :: Int -> IO (FieldType "color" VkDebugUtilsLabelEXT)
f Int
i
                                            = Ptr VkDebugUtilsLabelEXT -> Int -> IO Float
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDebugUtilsLabelEXT -> Ptr VkDebugUtilsLabelEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDebugUtilsLabelEXT
x) Int
i ::
                                                IO (FieldType "color" VkDebugUtilsLabelEXT)
                                        in
                                        IO [Float] -> [Float]
forall a. IO a -> a
unsafeDupablePerformIO (IO [Float] -> [Float])
-> ([Int] -> IO [Float]) -> [Int] -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> IO Float) -> [Int] -> IO [Float]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Int -> IO Float
Int -> IO (FieldType "color" VkDebugUtilsLabelEXT)
f ([Int] -> [Float]) -> [Int] -> [Float]
forall a b. (a -> b) -> a -> b
$
                                          (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\ Int
i -> Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
s) [Int
0 .. Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1])
                                     ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
']')
                                  ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'