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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.SampleLocation
       (VkSampleLocationEXT(..), VkSampleLocationsInfoEXT(..)) 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.Enum.SampleCountFlags (VkSampleCountFlagBits)
import           Graphics.Vulkan.Types.Enum.StructureType    (VkStructureType)
import           Graphics.Vulkan.Types.Struct.Extent         (VkExtent2D)
import           Graphics.Vulkan.Types.Struct.Image          (VkImageMemoryBarrier)
import           System.IO.Unsafe                            (unsafeDupablePerformIO)

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

instance {-# OVERLAPPING #-} HasField "x" VkSampleLocationEXT where
        type FieldType "x" VkSampleLocationEXT = Float
{-# LINE 78 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldOptional "x" VkSampleLocationEXT = 'False -- ' closing tick for hsc2hs
        type FieldOffset "x" VkSampleLocationEXT =
             (0)
{-# LINE 81 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "x" VkSampleLocationEXT = 'False -- ' closing tick for hsc2hs

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

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

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

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

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

instance {-# OVERLAPPING #-} HasField "y" VkSampleLocationEXT where
        type FieldType "y" VkSampleLocationEXT = Float
{-# LINE 108 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldOptional "y" VkSampleLocationEXT = 'False -- ' closing tick for hsc2hs
        type FieldOffset "y" VkSampleLocationEXT =
             (4)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "y" VkSampleLocationEXT = 'False -- ' closing tick for hsc2hs

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

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

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

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

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

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

-- | > typedef struct VkSampleLocationsInfoEXT {
--   >     VkStructureType sType;
--   >     const void*                      pNext;
--   >     VkSampleCountFlagBits            sampleLocationsPerPixel;
--   >     VkExtent2D                       sampleLocationGridSize;
--   >     uint32_t                         sampleLocationsCount;
--   >     const VkSampleLocationEXT* pSampleLocations;
--   > } VkSampleLocationsInfoEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSampleLocationsInfoEXT VkSampleLocationsInfoEXT registry at www.khronos.org>
data VkSampleLocationsInfoEXT = VkSampleLocationsInfoEXT# Addr#
                                                          ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkSampleLocationsInfoEXT where
        type StructFields VkSampleLocationsInfoEXT =
             '["sType", "pNext", "sampleLocationsPerPixel", -- ' closing tick for hsc2hs
               "sampleLocationGridSize", "sampleLocationsCount",
               "pSampleLocations"]
        type CUnionType VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs
        type StructExtends VkSampleLocationsInfoEXT =
             '[VkImageMemoryBarrier] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkSampleLocationsInfoEXT where
        type FieldType "sType" VkSampleLocationsInfoEXT = VkStructureType
        type FieldOptional "sType" VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkSampleLocationsInfoEXT =
             (0)
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "sType" VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO (FieldType "sType" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
0)
{-# LINE 230 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkSampleLocationsInfoEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "sType" VkSampleLocationsInfoEXT -> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
0)
{-# LINE 236 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkSampleLocationsInfoEXT where
        type FieldType "pNext" VkSampleLocationsInfoEXT = Ptr Void
        type FieldOptional "pNext" VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkSampleLocationsInfoEXT =
             (8)
{-# LINE 243 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "pNext" VkSampleLocationsInfoEXT = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO (FieldType "pNext" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
8)
{-# LINE 261 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkSampleLocationsInfoEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "pNext" VkSampleLocationsInfoEXT -> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
8)
{-# LINE 267 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "sampleLocationsPerPixel" VkSampleLocationsInfoEXT where
        type FieldType "sampleLocationsPerPixel" VkSampleLocationsInfoEXT =
             VkSampleCountFlagBits
        type FieldOptional "sampleLocationsPerPixel"
               VkSampleLocationsInfoEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sampleLocationsPerPixel" VkSampleLocationsInfoEXT
             =
             (16)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "sampleLocationsPerPixel"
               VkSampleLocationsInfoEXT
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO
     (FieldType "sampleLocationsPerPixel" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO VkSampleCountFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
16)
{-# LINE 300 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sampleLocationsPerPixel" VkSampleLocationsInfoEXT
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "sampleLocationsPerPixel" VkSampleLocationsInfoEXT
-> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT
-> Int -> VkSampleCountFlagBits -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
16)
{-# LINE 307 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "sampleLocationGridSize" VkSampleLocationsInfoEXT where
        type FieldType "sampleLocationGridSize" VkSampleLocationsInfoEXT =
             VkExtent2D
        type FieldOptional "sampleLocationGridSize"
               VkSampleLocationsInfoEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sampleLocationGridSize" VkSampleLocationsInfoEXT
             =
             (20)
{-# LINE 318 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "sampleLocationGridSize" VkSampleLocationsInfoEXT
             = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
20)
{-# LINE 327 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO (FieldType "sampleLocationGridSize" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO VkExtent2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
20)
{-# LINE 339 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sampleLocationGridSize" VkSampleLocationsInfoEXT
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "sampleLocationGridSize" VkSampleLocationsInfoEXT
-> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> VkExtent2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
20)
{-# LINE 346 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "sampleLocationsCount" VkSampleLocationsInfoEXT where
        type FieldType "sampleLocationsCount" VkSampleLocationsInfoEXT =
             Word32
        type FieldOptional "sampleLocationsCount" VkSampleLocationsInfoEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sampleLocationsCount" VkSampleLocationsInfoEXT =
             (28)
{-# LINE 355 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "sampleLocationsCount" VkSampleLocationsInfoEXT =
             'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset
          = (Int
28)
{-# LINE 364 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO (FieldType "sampleLocationsCount" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
28)
{-# LINE 375 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sampleLocationsCount" VkSampleLocationsInfoEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "sampleLocationsCount" VkSampleLocationsInfoEXT
-> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
28)
{-# LINE 381 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pSampleLocations" VkSampleLocationsInfoEXT where
        type FieldType "pSampleLocations" VkSampleLocationsInfoEXT =
             Ptr VkSampleLocationEXT
        type FieldOptional "pSampleLocations" VkSampleLocationsInfoEXT =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "pSampleLocations" VkSampleLocationsInfoEXT =
             (32)
{-# LINE 390 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}
        type FieldIsArray "pSampleLocations" VkSampleLocationsInfoEXT =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkSampleLocationsInfoEXT
-> IO (FieldType "pSampleLocations" VkSampleLocationsInfoEXT)
readField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT -> Int -> IO (Ptr VkSampleLocationEXT)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSampleLocationsInfoEXT
p (Int
32)
{-# LINE 410 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pSampleLocations" VkSampleLocationsInfoEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkSampleLocationsInfoEXT
-> FieldType "pSampleLocations" VkSampleLocationsInfoEXT -> IO ()
writeField Ptr VkSampleLocationsInfoEXT
p
          = Ptr VkSampleLocationsInfoEXT
-> Int -> Ptr VkSampleLocationEXT -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSampleLocationsInfoEXT
p (Int
32)
{-# LINE 416 "src-gen/Graphics/Vulkan/Types/Struct/SampleLocation.hsc" #-}

instance Show VkSampleLocationsInfoEXT where
        showsPrec :: Int -> VkSampleLocationsInfoEXT -> ShowS
showsPrec Int
d VkSampleLocationsInfoEXT
x
          = String -> ShowS
showString String
"VkSampleLocationsInfoEXT {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"sType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkStructureType -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSampleLocationsInfoEXT
-> FieldType "sType" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkSampleLocationsInfoEXT
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
"pNext = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Ptr Void -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSampleLocationsInfoEXT
-> FieldType "pNext" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkSampleLocationsInfoEXT
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
"sampleLocationsPerPixel = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkSampleCountFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSampleLocationsInfoEXT
-> FieldType "sampleLocationsPerPixel" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sampleLocationsPerPixel" VkSampleLocationsInfoEXT
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
"sampleLocationGridSize = " 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 (VkSampleLocationsInfoEXT
-> FieldType "sampleLocationGridSize" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sampleLocationGridSize" VkSampleLocationsInfoEXT
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
"sampleLocationsCount = " 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 (VkSampleLocationsInfoEXT
-> FieldType "sampleLocationsCount" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sampleLocationsCount" VkSampleLocationsInfoEXT
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
"pSampleLocations = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                              Int -> Ptr VkSampleLocationEXT -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSampleLocationsInfoEXT
-> FieldType "pSampleLocations" VkSampleLocationsInfoEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pSampleLocations" VkSampleLocationsInfoEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                                Char -> ShowS
showChar Char
'}'