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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.SubresourceLayout
       (VkSubresourceLayout(..)) 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.BaseTypes  (VkDeviceSize)
import           System.IO.Unsafe                 (unsafeDupablePerformIO)

-- | > typedef struct VkSubresourceLayout {
--   >     VkDeviceSize           offset;
--   >     VkDeviceSize           size;
--   >     VkDeviceSize           rowPitch;
--   >     VkDeviceSize           arrayPitch;
--   >     VkDeviceSize           depthPitch;
--   > } VkSubresourceLayout;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSubresourceLayout VkSubresourceLayout registry at www.khronos.org>
data VkSubresourceLayout = VkSubresourceLayout# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkSubresourceLayout where
        type StructFields VkSubresourceLayout =
             '["offset", "size", "rowPitch", "arrayPitch", "depthPitch"] -- ' closing tick for hsc2hs
        type CUnionType VkSubresourceLayout = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkSubresourceLayout = 'True -- ' closing tick for hsc2hs
        type StructExtends VkSubresourceLayout = '[] -- ' closing tick for hsc2hs

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

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

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

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

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

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

instance {-# OVERLAPPING #-} HasField "size" VkSubresourceLayout
         where
        type FieldType "size" VkSubresourceLayout = VkDeviceSize
        type FieldOptional "size" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs
        type FieldOffset "size" VkSubresourceLayout =
             (8)
{-# LINE 114 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}
        type FieldIsArray "size" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSubresourceLayout
-> IO (FieldType "size" VkSubresourceLayout)
readField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSubresourceLayout
p (Int
8)
{-# LINE 132 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "size" VkSubresourceLayout where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSubresourceLayout
-> FieldType "size" VkSubresourceLayout -> IO ()
writeField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSubresourceLayout
p (Int
8)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "rowPitch" VkSubresourceLayout where
        type FieldType "rowPitch" VkSubresourceLayout = VkDeviceSize
        type FieldOptional "rowPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs
        type FieldOffset "rowPitch" VkSubresourceLayout =
             (16)
{-# LINE 145 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}
        type FieldIsArray "rowPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSubresourceLayout
-> IO (FieldType "rowPitch" VkSubresourceLayout)
readField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSubresourceLayout
p (Int
16)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "rowPitch" VkSubresourceLayout where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSubresourceLayout
-> FieldType "rowPitch" VkSubresourceLayout -> IO ()
writeField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSubresourceLayout
p (Int
16)
{-# LINE 169 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "arrayPitch" VkSubresourceLayout where
        type FieldType "arrayPitch" VkSubresourceLayout = VkDeviceSize
        type FieldOptional "arrayPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs
        type FieldOffset "arrayPitch" VkSubresourceLayout =
             (24)
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}
        type FieldIsArray "arrayPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSubresourceLayout
-> IO (FieldType "arrayPitch" VkSubresourceLayout)
readField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSubresourceLayout
p (Int
24)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "arrayPitch" VkSubresourceLayout where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSubresourceLayout
-> FieldType "arrayPitch" VkSubresourceLayout -> IO ()
writeField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSubresourceLayout
p (Int
24)
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "depthPitch" VkSubresourceLayout where
        type FieldType "depthPitch" VkSubresourceLayout = VkDeviceSize
        type FieldOptional "depthPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs
        type FieldOffset "depthPitch" VkSubresourceLayout =
             (32)
{-# LINE 207 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}
        type FieldIsArray "depthPitch" VkSubresourceLayout = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSubresourceLayout
-> IO (FieldType "depthPitch" VkSubresourceLayout)
readField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSubresourceLayout
p (Int
32)
{-# LINE 225 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "depthPitch" VkSubresourceLayout where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSubresourceLayout
-> FieldType "depthPitch" VkSubresourceLayout -> IO ()
writeField Ptr VkSubresourceLayout
p
          = Ptr VkSubresourceLayout -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSubresourceLayout
p (Int
32)
{-# LINE 231 "src-gen/Graphics/Vulkan/Types/Struct/SubresourceLayout.hsc" #-}

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