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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.PastPresentationTimingGOOGLE
       (VkPastPresentationTimingGOOGLE(..)) where
import           Foreign.Storable                 (Storable (..))
import           GHC.Base                         (Addr#, ByteArray#,
                                                   byteArrayContents#,
                                                   plusAddr#)
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           System.IO.Unsafe                 (unsafeDupablePerformIO)

-- | > typedef struct VkPastPresentationTimingGOOGLE {
--   >     uint32_t                         presentID;
--   >     uint64_t                         desiredPresentTime;
--   >     uint64_t                         actualPresentTime;
--   >     uint64_t                         earliestPresentTime;
--   >     uint64_t                         presentMargin;
--   > } VkPastPresentationTimingGOOGLE;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkPastPresentationTimingGOOGLE VkPastPresentationTimingGOOGLE registry at www.khronos.org>
data VkPastPresentationTimingGOOGLE = VkPastPresentationTimingGOOGLE# Addr#
                                                                      ByteArray#

instance Eq VkPastPresentationTimingGOOGLE where
        (VkPastPresentationTimingGOOGLE# Addr#
a ByteArray#
_) == :: VkPastPresentationTimingGOOGLE
-> VkPastPresentationTimingGOOGLE -> Bool
==
          x :: VkPastPresentationTimingGOOGLE
x@(VkPastPresentationTimingGOOGLE# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkPastPresentationTimingGOOGLE -> Int
forall a. Storable a => a -> Int
sizeOf VkPastPresentationTimingGOOGLE
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkPastPresentationTimingGOOGLE
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkPastPresentationTimingGOOGLE
VkPastPresentationTimingGOOGLE#
              (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
              ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkPastPresentationTimingGOOGLE where
        type StructFields VkPastPresentationTimingGOOGLE =
             '["presentID", "desiredPresentTime", "actualPresentTime", -- ' closing tick for hsc2hs
               "earliestPresentTime", "presentMargin"]
        type CUnionType VkPastPresentationTimingGOOGLE = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkPastPresentationTimingGOOGLE = 'False -- ' closing tick for hsc2hs
        type StructExtends VkPastPresentationTimingGOOGLE = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "presentID" VkPastPresentationTimingGOOGLE where
        type FieldType "presentID" VkPastPresentationTimingGOOGLE = Word32
        type FieldOptional "presentID" VkPastPresentationTimingGOOGLE =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "presentID" VkPastPresentationTimingGOOGLE =
             (0)
{-# LINE 89 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}
        type FieldIsArray "presentID" VkPastPresentationTimingGOOGLE =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkPastPresentationTimingGOOGLE
-> IO (FieldType "presentID" VkPastPresentationTimingGOOGLE)
readField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
0)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "presentID" VkPastPresentationTimingGOOGLE where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPastPresentationTimingGOOGLE
-> FieldType "presentID" VkPastPresentationTimingGOOGLE -> IO ()
writeField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
0)
{-# LINE 115 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "desiredPresentTime" VkPastPresentationTimingGOOGLE where
        type FieldType "desiredPresentTime" VkPastPresentationTimingGOOGLE
             = Word64
        type FieldOptional "desiredPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "desiredPresentTime"
               VkPastPresentationTimingGOOGLE
             =
             (8)
{-# LINE 127 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}
        type FieldIsArray "desiredPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkPastPresentationTimingGOOGLE
-> IO
     (FieldType "desiredPresentTime" VkPastPresentationTimingGOOGLE)
readField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
8)
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "desiredPresentTime" VkPastPresentationTimingGOOGLE
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPastPresentationTimingGOOGLE
-> FieldType "desiredPresentTime" VkPastPresentationTimingGOOGLE
-> IO ()
writeField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
8)
{-# LINE 156 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "actualPresentTime" VkPastPresentationTimingGOOGLE where
        type FieldType "actualPresentTime" VkPastPresentationTimingGOOGLE =
             Word64
        type FieldOptional "actualPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "actualPresentTime" VkPastPresentationTimingGOOGLE
             =
             (16)
{-# LINE 167 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}
        type FieldIsArray "actualPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkPastPresentationTimingGOOGLE
-> IO
     (FieldType "actualPresentTime" VkPastPresentationTimingGOOGLE)
readField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
16)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "actualPresentTime" VkPastPresentationTimingGOOGLE
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPastPresentationTimingGOOGLE
-> FieldType "actualPresentTime" VkPastPresentationTimingGOOGLE
-> IO ()
writeField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
16)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "earliestPresentTime" VkPastPresentationTimingGOOGLE where
        type FieldType "earliestPresentTime" VkPastPresentationTimingGOOGLE
             = Word64
        type FieldOptional "earliestPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "earliestPresentTime"
               VkPastPresentationTimingGOOGLE
             =
             (24)
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}
        type FieldIsArray "earliestPresentTime"
               VkPastPresentationTimingGOOGLE
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
24)
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "earliestPresentTime" VkPastPresentationTimingGOOGLE
         where
        {-# NOINLINE getField #-}
        getField :: VkPastPresentationTimingGOOGLE
-> FieldType "earliestPresentTime" VkPastPresentationTimingGOOGLE
getField VkPastPresentationTimingGOOGLE
x
          = IO Word64 -> Word64
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkPastPresentationTimingGOOGLE
-> Ptr VkPastPresentationTimingGOOGLE
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkPastPresentationTimingGOOGLE
x) (Int
24))
{-# LINE 226 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkPastPresentationTimingGOOGLE
-> IO
     (FieldType "earliestPresentTime" VkPastPresentationTimingGOOGLE)
readField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
24)
{-# LINE 230 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "earliestPresentTime" VkPastPresentationTimingGOOGLE
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPastPresentationTimingGOOGLE
-> FieldType "earliestPresentTime" VkPastPresentationTimingGOOGLE
-> IO ()
writeField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
24)
{-# LINE 237 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "presentMargin" VkPastPresentationTimingGOOGLE where
        type FieldType "presentMargin" VkPastPresentationTimingGOOGLE =
             Word64
        type FieldOptional "presentMargin" VkPastPresentationTimingGOOGLE =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "presentMargin" VkPastPresentationTimingGOOGLE =
             (32)
{-# LINE 246 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}
        type FieldIsArray "presentMargin" VkPastPresentationTimingGOOGLE =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
32)
{-# LINE 255 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "presentMargin" VkPastPresentationTimingGOOGLE where
        {-# NOINLINE getField #-}
        getField :: VkPastPresentationTimingGOOGLE
-> FieldType "presentMargin" VkPastPresentationTimingGOOGLE
getField VkPastPresentationTimingGOOGLE
x
          = IO Word64 -> Word64
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkPastPresentationTimingGOOGLE
-> Ptr VkPastPresentationTimingGOOGLE
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkPastPresentationTimingGOOGLE
x) (Int
32))
{-# LINE 262 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkPastPresentationTimingGOOGLE
-> IO (FieldType "presentMargin" VkPastPresentationTimingGOOGLE)
readField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> IO Word64
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
32)
{-# LINE 266 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "presentMargin" VkPastPresentationTimingGOOGLE where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPastPresentationTimingGOOGLE
-> FieldType "presentMargin" VkPastPresentationTimingGOOGLE
-> IO ()
writeField Ptr VkPastPresentationTimingGOOGLE
p
          = Ptr VkPastPresentationTimingGOOGLE -> Int -> Word64 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPastPresentationTimingGOOGLE
p (Int
32)
{-# LINE 272 "src-gen/Graphics/Vulkan/Types/Struct/PastPresentationTimingGOOGLE.hsc" #-}

instance Show VkPastPresentationTimingGOOGLE where
        showsPrec :: Int -> VkPastPresentationTimingGOOGLE -> ShowS
showsPrec Int
d VkPastPresentationTimingGOOGLE
x
          = String -> ShowS
showString String
"VkPastPresentationTimingGOOGLE {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"presentID = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkPastPresentationTimingGOOGLE
-> FieldType "presentID" VkPastPresentationTimingGOOGLE
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"presentID" VkPastPresentationTimingGOOGLE
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
"desiredPresentTime = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Word64 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkPastPresentationTimingGOOGLE
-> FieldType "desiredPresentTime" VkPastPresentationTimingGOOGLE
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"desiredPresentTime" VkPastPresentationTimingGOOGLE
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
"actualPresentTime = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> Word64 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkPastPresentationTimingGOOGLE
-> FieldType "actualPresentTime" VkPastPresentationTimingGOOGLE
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"actualPresentTime" VkPastPresentationTimingGOOGLE
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
"earliestPresentTime = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                  Int -> Word64 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkPastPresentationTimingGOOGLE
-> FieldType "earliestPresentTime" VkPastPresentationTimingGOOGLE
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"earliestPresentTime" VkPastPresentationTimingGOOGLE
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
"presentMargin = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                        Int -> Word64 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkPastPresentationTimingGOOGLE
-> FieldType "presentMargin" VkPastPresentationTimingGOOGLE
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"presentMargin" VkPastPresentationTimingGOOGLE
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'