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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Offset
       (VkOffset2D(..), VkOffset3D(..)) 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 VkOffset2D {
--   >     int32_t        x;
--   >     int32_t        y;
--   > } VkOffset2D;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkOffset2D VkOffset2D registry at www.khronos.org>
data VkOffset2D = VkOffset2D# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkOffset2D where
        type StructFields VkOffset2D = '["x", "y"] -- ' closing tick for hsc2hs
        type CUnionType VkOffset2D = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkOffset2D = 'False -- ' closing tick for hsc2hs
        type StructExtends VkOffset2D = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "x" VkOffset2D where
        type FieldType "x" VkOffset2D = Int32
        type FieldOptional "x" VkOffset2D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "x" VkOffset2D =
             (0)
{-# LINE 77 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}
        type FieldIsArray "x" VkOffset2D = '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/Offset.hsc" #-}

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

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

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

instance {-# OVERLAPPING #-} HasField "y" VkOffset2D where
        type FieldType "y" VkOffset2D = Int32
        type FieldOptional "y" VkOffset2D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "y" VkOffset2D =
             (4)
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}
        type FieldIsArray "y" VkOffset2D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkOffset2D -> IO (FieldType "y" VkOffset2D)
readField Ptr VkOffset2D
p = Ptr VkOffset2D -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkOffset2D
p (Int
4)
{-# LINE 119 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "y" VkOffset2D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkOffset2D -> FieldType "y" VkOffset2D -> IO ()
writeField Ptr VkOffset2D
p = Ptr VkOffset2D -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkOffset2D
p (Int
4)
{-# LINE 123 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

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

-- | > typedef struct VkOffset3D {
--   >     int32_t        x;
--   >     int32_t        y;
--   >     int32_t        z;
--   > } VkOffset3D;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkOffset3D VkOffset3D registry at www.khronos.org>
data VkOffset3D = VkOffset3D# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkOffset3D where
        type StructFields VkOffset3D = '["x", "y", "z"] -- ' closing tick for hsc2hs
        type CUnionType VkOffset3D = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkOffset3D = 'False -- ' closing tick for hsc2hs
        type StructExtends VkOffset3D = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "x" VkOffset3D where
        type FieldType "x" VkOffset3D = Int32
        type FieldOptional "x" VkOffset3D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "x" VkOffset3D =
             (0)
{-# LINE 190 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}
        type FieldIsArray "x" VkOffset3D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkOffset3D -> IO (FieldType "x" VkOffset3D)
readField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkOffset3D
p (Int
0)
{-# LINE 206 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "x" VkOffset3D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkOffset3D -> FieldType "x" VkOffset3D -> IO ()
writeField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkOffset3D
p (Int
0)
{-# LINE 210 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} HasField "y" VkOffset3D where
        type FieldType "y" VkOffset3D = Int32
        type FieldOptional "y" VkOffset3D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "y" VkOffset3D =
             (4)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}
        type FieldIsArray "y" VkOffset3D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkOffset3D -> IO (FieldType "y" VkOffset3D)
readField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkOffset3D
p (Int
4)
{-# LINE 232 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "y" VkOffset3D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkOffset3D -> FieldType "y" VkOffset3D -> IO ()
writeField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkOffset3D
p (Int
4)
{-# LINE 236 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} HasField "z" VkOffset3D where
        type FieldType "z" VkOffset3D = Int32
        type FieldOptional "z" VkOffset3D = 'False -- ' closing tick for hsc2hs
        type FieldOffset "z" VkOffset3D =
             (8)
{-# LINE 242 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}
        type FieldIsArray "z" VkOffset3D = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkOffset3D -> IO (FieldType "z" VkOffset3D)
readField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkOffset3D
p (Int
8)
{-# LINE 258 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "z" VkOffset3D where
        {-# INLINE writeField #-}
        writeField :: Ptr VkOffset3D -> FieldType "z" VkOffset3D -> IO ()
writeField Ptr VkOffset3D
p = Ptr VkOffset3D -> Int -> Int32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkOffset3D
p (Int
8)
{-# LINE 262 "src-gen/Graphics/Vulkan/Types/Struct/Offset.hsc" #-}

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