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


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

-- | > typedef struct VkPushConstantRange {
--   >     VkShaderStageFlags     stageFlags;
--   >     uint32_t               offset;
--   >     uint32_t               size;
--   > } VkPushConstantRange;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkPushConstantRange VkPushConstantRange registry at www.khronos.org>
data VkPushConstantRange = VkPushConstantRange# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

instance {-# OVERLAPPING #-}
         HasField "stageFlags" VkPushConstantRange where
        type FieldType "stageFlags" VkPushConstantRange =
             VkShaderStageFlags
        type FieldOptional "stageFlags" VkPushConstantRange = 'False -- ' closing tick for hsc2hs
        type FieldOffset "stageFlags" VkPushConstantRange =
             (0)
{-# LINE 82 "src-gen/Graphics/Vulkan/Types/Struct/PushConstantRange.hsc" #-}
        type FieldIsArray "stageFlags" VkPushConstantRange = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkPushConstantRange
-> IO (FieldType "stageFlags" VkPushConstantRange)
readField Ptr VkPushConstantRange
p
          = Ptr VkPushConstantRange -> Int -> IO VkShaderStageFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkPushConstantRange
p (Int
0)
{-# LINE 100 "src-gen/Graphics/Vulkan/Types/Struct/PushConstantRange.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "stageFlags" VkPushConstantRange where
        {-# INLINE writeField #-}
        writeField :: Ptr VkPushConstantRange
-> FieldType "stageFlags" VkPushConstantRange -> IO ()
writeField Ptr VkPushConstantRange
p
          = Ptr VkPushConstantRange -> Int -> VkShaderStageFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkPushConstantRange
p (Int
0)
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/PushConstantRange.hsc" #-}

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

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

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

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

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

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

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

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

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

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

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

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

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