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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Extent
       (VkExtent2D(..), VkExtent3D(..)) 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 VkExtent2D {
--   >     uint32_t        width;
--   >     uint32_t        height;
--   > } VkExtent2D;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkExtent2D VkExtent2D registry at www.khronos.org>
data VkExtent2D = VkExtent2D# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkExtent2D where
        sizeOf :: VkExtent2D -> Int
sizeOf ~VkExtent2D
_ = (Int
8)
{-# LINE 42 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkExtent2D where
        type StructFields VkExtent2D = '["width", "height"] -- ' closing tick for hsc2hs
        type CUnionType VkExtent2D = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkExtent2D = 'False -- ' closing tick for hsc2hs
        type StructExtends VkExtent2D = '[] -- ' closing tick for hsc2hs

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

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

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

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

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

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

instance {-# OVERLAPPING #-} HasField "height" VkExtent2D where
        type FieldType "height" VkExtent2D = Word32
        type FieldOptional "height" VkExtent2D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "height" VkExtent2D =
             (4)
{-# LINE 104 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}
        type FieldIsArray "height" VkExtent2D = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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

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

instance {-# OVERLAPPING #-} CanWriteField "height" VkExtent2D
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExtent2D -> FieldType "height" VkExtent2D -> IO ()
writeField Ptr VkExtent2D
p
          = Ptr VkExtent2D -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExtent2D
p (Int
4)
{-# LINE 127 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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

-- | > typedef struct VkExtent3D {
--   >     uint32_t        width;
--   >     uint32_t        height;
--   >     uint32_t        depth;
--   > } VkExtent3D;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkExtent3D VkExtent3D registry at www.khronos.org>
data VkExtent3D = VkExtent3D# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkExtent3D where
        sizeOf :: VkExtent3D -> Int
sizeOf ~VkExtent3D
_ = (Int
12)
{-# LINE 160 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkExtent3D where
        type StructFields VkExtent3D = '["width", "height", "depth"] -- ' closing tick for hsc2hs
        type CUnionType VkExtent3D = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkExtent3D = 'False -- ' closing tick for hsc2hs
        type StructExtends VkExtent3D = '[] -- ' closing tick for hsc2hs

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

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

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

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

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

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

instance {-# OVERLAPPING #-} HasField "height" VkExtent3D where
        type FieldType "height" VkExtent3D = Word32
        type FieldOptional "height" VkExtent3D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "height" VkExtent3D =
             (4)
{-# LINE 222 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}
        type FieldIsArray "height" VkExtent3D = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 229 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkExtent3D -> IO (FieldType "height" VkExtent3D)
readField Ptr VkExtent3D
p
          = Ptr VkExtent3D -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExtent3D
p (Int
4)
{-# LINE 239 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "height" VkExtent3D
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExtent3D -> FieldType "height" VkExtent3D -> IO ()
writeField Ptr VkExtent3D
p
          = Ptr VkExtent3D -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExtent3D
p (Int
4)
{-# LINE 245 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

instance {-# OVERLAPPING #-} HasField "depth" VkExtent3D where
        type FieldType "depth" VkExtent3D = Word32
        type FieldOptional "depth" VkExtent3D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "depth" VkExtent3D =
             (8)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}
        type FieldIsArray "depth" VkExtent3D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkExtent3D -> IO (FieldType "depth" VkExtent3D)
readField Ptr VkExtent3D
p = Ptr VkExtent3D -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExtent3D
p (Int
8)
{-# LINE 267 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "depth" VkExtent3D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExtent3D -> FieldType "depth" VkExtent3D -> IO ()
writeField Ptr VkExtent3D
p
          = Ptr VkExtent3D -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExtent3D
p (Int
8)
{-# LINE 272 "src-gen/Graphics/Vulkan/Types/Struct/Extent.hsc" #-}

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