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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Rect
       (VkRect2D(..), VkRectLayerKHR(..)) 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.Struct.Extent (VkExtent2D)
import           Graphics.Vulkan.Types.Struct.Offset (VkOffset2D)
import           System.IO.Unsafe                    (unsafeDupablePerformIO)

-- | > typedef struct VkRect2D {
--   >     VkOffset2D     offset;
--   >     VkExtent2D     extent;
--   > } VkRect2D;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRect2D VkRect2D registry at www.khronos.org>
data VkRect2D = VkRect2D# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkRect2D where
        sizeOf :: VkRect2D -> Int
sizeOf ~VkRect2D
_ = (Int
16)
{-# LINE 44 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkRect2D -> Int
alignment ~VkRect2D
_ = Int
4
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkRect2D where
        type StructFields VkRect2D = '["offset", "extent"] -- ' closing tick for hsc2hs
        type CUnionType VkRect2D = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkRect2D = 'False -- ' closing tick for hsc2hs
        type StructExtends VkRect2D = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "offset" VkRect2D where
        type FieldType "offset" VkRect2D = VkOffset2D
        type FieldOptional "offset" VkRect2D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "offset" VkRect2D =
             (0)
{-# LINE 79 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}
        type FieldIsArray "offset" VkRect2D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkRect2D -> IO (FieldType "offset" VkRect2D)
readField Ptr VkRect2D
p = Ptr VkRect2D -> Int -> IO VkOffset2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkRect2D
p (Int
0)
{-# LINE 95 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "offset" VkRect2D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkRect2D -> FieldType "offset" VkRect2D -> IO ()
writeField Ptr VkRect2D
p = Ptr VkRect2D -> Int -> VkOffset2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkRect2D
p (Int
0)
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} HasField "extent" VkRect2D where
        type FieldType "extent" VkRect2D = VkExtent2D
        type FieldOptional "extent" VkRect2D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "extent" VkRect2D =
             (8)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}
        type FieldIsArray "extent" VkRect2D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkRect2D -> IO (FieldType "extent" VkRect2D)
readField Ptr VkRect2D
p = Ptr VkRect2D -> Int -> IO VkExtent2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkRect2D
p (Int
8)
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "extent" VkRect2D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkRect2D -> FieldType "extent" VkRect2D -> IO ()
writeField Ptr VkRect2D
p = Ptr VkRect2D -> Int -> VkExtent2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkRect2D
p (Int
8)
{-# LINE 125 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance Show VkRect2D where
        showsPrec :: Int -> VkRect2D -> ShowS
showsPrec Int
d VkRect2D
x
          = String -> ShowS
showString String
"VkRect2D {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"offset = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkOffset2D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkRect2D -> FieldType "offset" VkRect2D
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"offset" VkRect2D
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
"extent = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> VkExtent2D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkRect2D -> FieldType "extent" VkRect2D
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"extent" VkRect2D
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

-- | > typedef struct VkRectLayerKHR {
--   >     VkOffset2D                       offset;
--   >     VkExtent2D                       extent;
--   >     uint32_t                         layer;
--   > } VkRectLayerKHR;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRectLayerKHR VkRectLayerKHR registry at www.khronos.org>
data VkRectLayerKHR = VkRectLayerKHR# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkRectLayerKHR where
        sizeOf :: VkRectLayerKHR -> Int
sizeOf ~VkRectLayerKHR
_ = (Int
20)
{-# LINE 158 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkRectLayerKHR -> Int
alignment ~VkRectLayerKHR
_ = Int
4
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkRectLayerKHR where
        type StructFields VkRectLayerKHR = '["offset", "extent", "layer"] -- ' closing tick for hsc2hs
        type CUnionType VkRectLayerKHR = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkRectLayerKHR = 'False -- ' closing tick for hsc2hs
        type StructExtends VkRectLayerKHR = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "offset" VkRectLayerKHR where
        type FieldType "offset" VkRectLayerKHR = VkOffset2D
        type FieldOptional "offset" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "offset" VkRectLayerKHR =
             (0)
{-# LINE 193 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}
        type FieldIsArray "offset" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkRectLayerKHR -> IO (FieldType "offset" VkRectLayerKHR)
readField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> IO VkOffset2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkRectLayerKHR
p (Int
0)
{-# LINE 211 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "offset" VkRectLayerKHR
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkRectLayerKHR -> FieldType "offset" VkRectLayerKHR -> IO ()
writeField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> VkOffset2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkRectLayerKHR
p (Int
0)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} HasField "extent" VkRectLayerKHR where
        type FieldType "extent" VkRectLayerKHR = VkExtent2D
        type FieldOptional "extent" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "extent" VkRectLayerKHR =
             (8)
{-# LINE 223 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}
        type FieldIsArray "extent" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkRectLayerKHR -> IO (FieldType "extent" VkRectLayerKHR)
readField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> IO VkExtent2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkRectLayerKHR
p (Int
8)
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "extent" VkRectLayerKHR
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkRectLayerKHR -> FieldType "extent" VkRectLayerKHR -> IO ()
writeField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> VkExtent2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkRectLayerKHR
p (Int
8)
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} HasField "layer" VkRectLayerKHR where
        type FieldType "layer" VkRectLayerKHR = Word32
        type FieldOptional "layer" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "layer" VkRectLayerKHR =
             (16)
{-# LINE 253 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}
        type FieldIsArray "layer" VkRectLayerKHR = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkRectLayerKHR -> IO (FieldType "layer" VkRectLayerKHR)
readField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkRectLayerKHR
p (Int
16)
{-# LINE 271 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "layer" VkRectLayerKHR
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkRectLayerKHR -> FieldType "layer" VkRectLayerKHR -> IO ()
writeField Ptr VkRectLayerKHR
p
          = Ptr VkRectLayerKHR -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkRectLayerKHR
p (Int
16)
{-# LINE 277 "src-gen/Graphics/Vulkan/Types/Struct/Rect.hsc" #-}

instance Show VkRectLayerKHR where
        showsPrec :: Int -> VkRectLayerKHR -> ShowS
showsPrec Int
d VkRectLayerKHR
x
          = String -> ShowS
showString String
"VkRectLayerKHR {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"offset = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkOffset2D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkRectLayerKHR -> FieldType "offset" VkRectLayerKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"offset" VkRectLayerKHR
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
"extent = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> VkExtent2D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkRectLayerKHR -> FieldType "extent" VkRectLayerKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"extent" VkRectLayerKHR
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
"layer = " 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 (VkRectLayerKHR -> FieldType "layer" VkRectLayerKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"layer" VkRectLayerKHR
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'