{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.MappedMemoryRange
(VkMappedMemoryRange(..)) 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 Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles (VkDeviceMemory)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkMappedMemoryRange = VkMappedMemoryRange# Addr# ByteArray#
instance Eq VkMappedMemoryRange where
(VkMappedMemoryRange# Addr#
a ByteArray#
_) == :: VkMappedMemoryRange -> VkMappedMemoryRange -> Bool
== x :: VkMappedMemoryRange
x@(VkMappedMemoryRange# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkMappedMemoryRange -> Int
forall a. Storable a => a -> Int
sizeOf VkMappedMemoryRange
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkMappedMemoryRange where
(VkMappedMemoryRange# Addr#
a ByteArray#
_) compare :: VkMappedMemoryRange -> VkMappedMemoryRange -> Ordering
`compare` x :: VkMappedMemoryRange
x@(VkMappedMemoryRange# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkMappedMemoryRange -> Int
forall a. Storable a => a -> Int
sizeOf VkMappedMemoryRange
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkMappedMemoryRange where
sizeOf :: VkMappedMemoryRange -> Int
sizeOf ~VkMappedMemoryRange
_ = (Int
40)
{-# LINE 48 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkMappedMemoryRange -> Int
alignment ~VkMappedMemoryRange
_ = Int
8
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkMappedMemoryRange -> IO VkMappedMemoryRange
peek = Ptr VkMappedMemoryRange -> IO VkMappedMemoryRange
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkMappedMemoryRange -> VkMappedMemoryRange -> IO ()
poke = Ptr VkMappedMemoryRange -> VkMappedMemoryRange -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkMappedMemoryRange where
unsafeAddr :: VkMappedMemoryRange -> Addr#
unsafeAddr (VkMappedMemoryRange# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkMappedMemoryRange -> ByteArray#
unsafeByteArray (VkMappedMemoryRange# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkMappedMemoryRange
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkMappedMemoryRange
VkMappedMemoryRange# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkMappedMemoryRange where
type StructFields VkMappedMemoryRange =
'["sType", "pNext", "memory", "offset", "size"]
type CUnionType VkMappedMemoryRange = 'False
type ReturnedOnly VkMappedMemoryRange = 'False
type StructExtends VkMappedMemoryRange = '[]
instance {-# OVERLAPPING #-} HasField "sType" VkMappedMemoryRange
where
type FieldType "sType" VkMappedMemoryRange = VkStructureType
type FieldOptional "sType" VkMappedMemoryRange = 'False
type FieldOffset "sType" VkMappedMemoryRange =
(0)
{-# LINE 85 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
type FieldIsArray "sType" VkMappedMemoryRange = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 92 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkMappedMemoryRange where
{-# NOINLINE getField #-}
getField :: VkMappedMemoryRange -> FieldType "sType" VkMappedMemoryRange
getField VkMappedMemoryRange
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMappedMemoryRange -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMappedMemoryRange -> Ptr VkMappedMemoryRange
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMappedMemoryRange
x) (Int
0))
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMappedMemoryRange
-> IO (FieldType "sType" VkMappedMemoryRange)
readField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMappedMemoryRange
p (Int
0)
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkMappedMemoryRange where
{-# INLINE writeField #-}
writeField :: Ptr VkMappedMemoryRange
-> FieldType "sType" VkMappedMemoryRange -> IO ()
writeField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMappedMemoryRange
p (Int
0)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-} HasField "pNext" VkMappedMemoryRange
where
type FieldType "pNext" VkMappedMemoryRange = Ptr Void
type FieldOptional "pNext" VkMappedMemoryRange = 'False
type FieldOffset "pNext" VkMappedMemoryRange =
(8)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
type FieldIsArray "pNext" VkMappedMemoryRange = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 123 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkMappedMemoryRange where
{-# NOINLINE getField #-}
getField :: VkMappedMemoryRange -> FieldType "pNext" VkMappedMemoryRange
getField VkMappedMemoryRange
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMappedMemoryRange -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMappedMemoryRange -> Ptr VkMappedMemoryRange
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMappedMemoryRange
x) (Int
8))
{-# LINE 130 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMappedMemoryRange
-> IO (FieldType "pNext" VkMappedMemoryRange)
readField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMappedMemoryRange
p (Int
8)
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkMappedMemoryRange where
{-# INLINE writeField #-}
writeField :: Ptr VkMappedMemoryRange
-> FieldType "pNext" VkMappedMemoryRange -> IO ()
writeField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMappedMemoryRange
p (Int
8)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-} HasField "memory" VkMappedMemoryRange
where
type FieldType "memory" VkMappedMemoryRange = VkDeviceMemory
type FieldOptional "memory" VkMappedMemoryRange = 'False
type FieldOffset "memory" VkMappedMemoryRange =
(16)
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
type FieldIsArray "memory" VkMappedMemoryRange = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memory" VkMappedMemoryRange where
{-# NOINLINE getField #-}
getField :: VkMappedMemoryRange -> FieldType "memory" VkMappedMemoryRange
getField VkMappedMemoryRange
x
= IO VkDeviceMemory -> VkDeviceMemory
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMappedMemoryRange -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMappedMemoryRange -> Ptr VkMappedMemoryRange
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMappedMemoryRange
x) (Int
16))
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMappedMemoryRange
-> IO (FieldType "memory" VkMappedMemoryRange)
readField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMappedMemoryRange
p (Int
16)
{-# LINE 165 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memory" VkMappedMemoryRange where
{-# INLINE writeField #-}
writeField :: Ptr VkMappedMemoryRange
-> FieldType "memory" VkMappedMemoryRange -> IO ()
writeField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> VkDeviceMemory -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMappedMemoryRange
p (Int
16)
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-} HasField "offset" VkMappedMemoryRange
where
type FieldType "offset" VkMappedMemoryRange = VkDeviceSize
type FieldOptional "offset" VkMappedMemoryRange = 'False
type FieldOffset "offset" VkMappedMemoryRange =
(24)
{-# LINE 178 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
type FieldIsArray "offset" VkMappedMemoryRange = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
24)
{-# LINE 185 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "offset" VkMappedMemoryRange where
{-# NOINLINE getField #-}
getField :: VkMappedMemoryRange -> FieldType "offset" VkMappedMemoryRange
getField VkMappedMemoryRange
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMappedMemoryRange -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMappedMemoryRange -> Ptr VkMappedMemoryRange
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMappedMemoryRange
x) (Int
24))
{-# LINE 192 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMappedMemoryRange
-> IO (FieldType "offset" VkMappedMemoryRange)
readField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMappedMemoryRange
p (Int
24)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "offset" VkMappedMemoryRange where
{-# INLINE writeField #-}
writeField :: Ptr VkMappedMemoryRange
-> FieldType "offset" VkMappedMemoryRange -> IO ()
writeField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMappedMemoryRange
p (Int
24)
{-# LINE 202 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-} HasField "size" VkMappedMemoryRange
where
type FieldType "size" VkMappedMemoryRange = VkDeviceSize
type FieldOptional "size" VkMappedMemoryRange = 'False
type FieldOffset "size" VkMappedMemoryRange =
(32)
{-# LINE 209 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
type FieldIsArray "size" VkMappedMemoryRange = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
32)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "size" VkMappedMemoryRange where
{-# NOINLINE getField #-}
getField :: VkMappedMemoryRange -> FieldType "size" VkMappedMemoryRange
getField VkMappedMemoryRange
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMappedMemoryRange -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMappedMemoryRange -> Ptr VkMappedMemoryRange
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMappedMemoryRange
x) (Int
32))
{-# LINE 223 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMappedMemoryRange
-> IO (FieldType "size" VkMappedMemoryRange)
readField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMappedMemoryRange
p (Int
32)
{-# LINE 227 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "size" VkMappedMemoryRange where
{-# INLINE writeField #-}
writeField :: Ptr VkMappedMemoryRange
-> FieldType "size" VkMappedMemoryRange -> IO ()
writeField Ptr VkMappedMemoryRange
p
= Ptr VkMappedMemoryRange -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMappedMemoryRange
p (Int
32)
{-# LINE 233 "src-gen/Graphics/Vulkan/Types/Struct/MappedMemoryRange.hsc" #-}
instance Show VkMappedMemoryRange where
showsPrec :: Int -> VkMappedMemoryRange -> ShowS
showsPrec Int
d VkMappedMemoryRange
x
= String -> ShowS
showString String
"VkMappedMemoryRange {" 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 (VkMappedMemoryRange -> FieldType "sType" VkMappedMemoryRange
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkMappedMemoryRange
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 (VkMappedMemoryRange -> FieldType "pNext" VkMappedMemoryRange
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkMappedMemoryRange
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
"memory = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkDeviceMemory -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMappedMemoryRange -> FieldType "memory" VkMappedMemoryRange
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memory" VkMappedMemoryRange
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 -> VkDeviceSize -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMappedMemoryRange -> FieldType "offset" VkMappedMemoryRange
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"offset" VkMappedMemoryRange
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 (VkMappedMemoryRange -> FieldType "size" VkMappedMemoryRange
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"size" VkMappedMemoryRange
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'