{-# LINE 1 "src/Gpu/Vulkan/Image/Core.hsc" #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}

module Gpu.Vulkan.Image.Core (

	-- * CREATE AND DESTROY
	create, destroy, I, CreateInfo, pattern CreateInfo,
	createInfoSType, createInfoPNext, createInfoFlags,
	createInfoImageType, createInfoFormat, createInfoExtent,
	createInfoMipLevels, createInfoArrayLayers, createInfoSamples,
	createInfoTiling, createInfoUsage, createInfoSharingMode,
	createInfoQueueFamilyIndexCount, createInfoPQueueFamilyIndices,
	createInfoInitialLayout,

	-- * MEMORY: REQUIREMENTS AND BINDING

	getMemoryRequirements, bindMemory,

	-- * MEMORY BARRIER

	MemoryBarrier, pattern MemoryBarrier,
	memoryBarrierSType, memoryBarrierPNext,
	memoryBarrierSrcAccessMask, memoryBarrierDstAccessMask,
	memoryBarrierOldLayout, memoryBarrierNewLayout,
	memoryBarrierSrcQueueFamilyIndex, memoryBarrierDstQueueFamilyIndex,
	memoryBarrierImage, memoryBarrierSubresourceRange,

	MemoryBarrier2, PtrMemoryBarrier2, pattern MemoryBarrier2,
	memoryBarrier2SType, memoryBarrier2PNext,
	memoryBarrier2SrcStageMask, memoryBarrier2SrcAccessMask,
	memoryBarrier2DstStageMask, memoryBarrier2DstAccessMask,
	memoryBarrier2OldLayout, memoryBarrier2NewLayout,
	memoryBarrier2SrcQueueFamilyIndex, memoryBarrier2DstQueueFamilyIndex,
	memoryBarrier2Image, memoryBarrier2SubresourceRange,

	-- ** SubresourceRange

	SubresourceRange, pattern SubresourceRange,
	subresourceRangeAspectMask, subresourceRangeBaseMipLevel,
	subresourceRangeLevelCount, subresourceRangeBaseArrayLayer,
	subresourceRangeLayerCount,

	-- * BLIT
	
	Blit, pattern Blit,
	blitSrcSubresource, blitSrcOffsets, blitDstSubresource, blitDstOffsets,

	Blit2, PtrBlit2, pattern Blit2,
	blit2SType, blit2PNext,
	blit2SrcSubresource, blit2SrcOffsets,
	blit2DstSubresource, blit2DstOffsets,

	-- ** SubresourceLayers

	SubresourceLayers, pattern SubresourceLayers,
	subresourceLayersAspectMask, subresourceLayersMipLevel,
	subresourceLayersBaseArrayLayer, subresourceLayersLayerCount,

	-- * Subresource

	Subresource, pattern Subresource,
	subresourceAspectMask, subresourceMipLevel,
	subresourceArrayLayer

	) where

import Foreign.Ptr
import Foreign.Marshal.Array
import Foreign.Storable
import Foreign.C.Struct
import Foreign.C.Struct.TypeSynonyms
import Data.Word
import Data.Int

import Gpu.Vulkan.Core
import Gpu.Vulkan.TypeSynonyms.Core
import Gpu.Vulkan.AllocationCallbacks.Core qualified as AllocationCallbacks
import {-# SOURCE #-} Gpu.Vulkan.Device.Core qualified as Device
import Gpu.Vulkan.Memory.Core qualified as Memory



struct "SubresourceRange" (20)
{-# LINE 87 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		4 [
{-# LINE 88 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("aspectMask", ''Word32,
{-# LINE 89 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 90 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 91 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("baseMipLevel", ''Word32,
{-# LINE 92 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 93 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 94 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("levelCount", ''Word32,
{-# LINE 95 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 96 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 97 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("baseArrayLayer", ''Word32,
{-# LINE 98 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 99 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]),
{-# LINE 100 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("layerCount", ''Word32,
{-# LINE 101 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 102 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]) ]
{-# LINE 103 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

data ITag
type I = Ptr ITag

sType :: Word32
{-# LINE 109 "src/Gpu/Vulkan/Image/Core.hsc" #-}
sType = 14
{-# LINE 110 "src/Gpu/Vulkan/Image/Core.hsc" #-}

struct "CreateInfo" (88) 8 [
{-# LINE 112 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p sType |]),
{-# LINE 114 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 116 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 117 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 118 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 119 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 120 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("imageType", ''Word32,
{-# LINE 121 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 122 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]),
{-# LINE 123 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("format", ''Word32,
{-# LINE 124 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 125 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 126 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("extent", ''Extent3d,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 28) |],
{-# LINE 128 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 28) |]),
{-# LINE 129 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("mipLevels", ''Word32,
{-# LINE 130 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 131 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 132 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("arrayLayers", ''Word32,
{-# LINE 133 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 44) |],
{-# LINE 134 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 44) |]),
{-# LINE 135 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("samples", ''Word32,
{-# LINE 136 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 137 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]),
{-# LINE 138 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("tiling", ''Word32,
{-# LINE 139 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 52) |],
{-# LINE 140 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 52) |]),
{-# LINE 141 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("usage", ''Word32,
{-# LINE 142 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 56) |],
{-# LINE 143 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 56) |]),
{-# LINE 144 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("sharingMode", ''Word32,
{-# LINE 145 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 60) |],
{-# LINE 146 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 60) |]),
{-# LINE 147 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("queueFamilyIndexCount", ''Word32,
{-# LINE 148 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 64) |],
{-# LINE 149 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 64) |]),
{-# LINE 150 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("pQueueFamilyIndices", ''PtrUint32T,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 72) |],
{-# LINE 152 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 72) |]),
{-# LINE 153 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("initialLayout", ''Word32,
{-# LINE 154 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 80) |],
{-# LINE 155 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 80) |]) ]
{-# LINE 156 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

foreign import ccall "vkCreateImage" create ::
	Device.D -> Ptr CreateInfo -> Ptr AllocationCallbacks.A -> Ptr I ->
	IO Int32
{-# LINE 161 "src/Gpu/Vulkan/Image/Core.hsc" #-}

foreign import ccall "vkGetImageMemoryRequirements" getMemoryRequirements ::
	Device.D -> I -> Ptr Memory.Requirements -> IO ()

foreign import ccall "vkBindImageMemory" bindMemory ::
	Device.D -> I -> Memory.M -> Word64 ->
{-# LINE 167 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	IO Int32
{-# LINE 168 "src/Gpu/Vulkan/Image/Core.hsc" #-}

mbType :: Word32
{-# LINE 170 "src/Gpu/Vulkan/Image/Core.hsc" #-}
mbType = 45
{-# LINE 171 "src/Gpu/Vulkan/Image/Core.hsc" #-}

struct "MemoryBarrier" (72)
{-# LINE 173 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		8 [
{-# LINE 174 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p mbType |]),
{-# LINE 176 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 178 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 179 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcAccessMask", ''Word32,
{-# LINE 180 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 181 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 182 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstAccessMask", ''Word32,
{-# LINE 183 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 184 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]),
{-# LINE 185 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("oldLayout", ''Word32,
{-# LINE 186 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 187 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 188 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("newLayout", ''Word32,
{-# LINE 189 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 28) |],
{-# LINE 190 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 28) |]),
{-# LINE 191 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcQueueFamilyIndex", ''Word32,
{-# LINE 192 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 193 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]),
{-# LINE 194 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstQueueFamilyIndex", ''Word32,
{-# LINE 195 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 36) |],
{-# LINE 196 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 36) |]),
{-# LINE 197 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("image", ''I,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 199 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 200 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("subresourceRange", ''SubresourceRange,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 202 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]) ]
{-# LINE 203 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

mbType2 :: Word32
{-# LINE 206 "src/Gpu/Vulkan/Image/Core.hsc" #-}
mbType2 = 1000314002
{-# LINE 207 "src/Gpu/Vulkan/Image/Core.hsc" #-}

struct "MemoryBarrier2" (96)
{-# LINE 209 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		8 [
{-# LINE 210 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p mbType2 |]),
{-# LINE 212 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 214 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 215 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcStageMask", ''Word64,
{-# LINE 216 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 217 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 218 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcAccessMask", ''Word64,
{-# LINE 219 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 220 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 221 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstStageMask", ''Word64,
{-# LINE 222 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 223 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]),
{-# LINE 224 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstAccessMask", ''Word64,
{-# LINE 225 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 226 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 227 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("oldLayout", ''Word32,
{-# LINE 228 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 229 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]),
{-# LINE 230 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("newLayout", ''Word32,
{-# LINE 231 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 52) |],
{-# LINE 232 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 52) |]),
{-# LINE 233 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcQueueFamilyIndex", ''Word32,
{-# LINE 234 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 56) |],
{-# LINE 235 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 56) |]),
{-# LINE 236 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstQueueFamilyIndex", ''Word32,
{-# LINE 237 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 60) |],
{-# LINE 238 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 60) |]),
{-# LINE 239 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("image", ''I,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 64) |],
{-# LINE 241 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 64) |]),
{-# LINE 242 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("subresourceRange", ''SubresourceRange,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 72) |],
{-# LINE 244 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 72) |]) ]
{-# LINE 245 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

type PtrMemoryBarrier2 = Ptr MemoryBarrier2

struct "SubresourceLayers" (16)
{-# LINE 250 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		4 [
{-# LINE 251 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("aspectMask", ''Word32,
{-# LINE 252 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 253 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 254 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("mipLevel", ''Word32,
{-# LINE 255 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 256 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 257 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("baseArrayLayer", ''Word32,
{-# LINE 258 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 259 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 260 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("layerCount", ''Word32,
{-# LINE 261 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 262 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]) ]
{-# LINE 263 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

foreign import ccall "vkDestroyImage" destroy ::
	Device.D -> I -> Ptr AllocationCallbacks.A -> IO ()

struct "Blit" (80) 4 [
{-# LINE 269 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcSubresource", ''SubresourceLayers,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 271 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 272 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcOffsets", ''ListOffset3d,
		[| \p -> peekArray 2 ((\hsc_ptr -> hsc_ptr `plusPtr` 16) p) |],
{-# LINE 274 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| \p os -> pokeArray
			((\hsc_ptr -> hsc_ptr `plusPtr` 16) p) $ take 2 os |]),
{-# LINE 276 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstSubresource", ''SubresourceLayers,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 278 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 279 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstOffsets", ''ListOffset3d,
		[| \p -> peekArray 2 ((\hsc_ptr -> hsc_ptr `plusPtr` 56) p) |],
{-# LINE 281 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| \p os -> pokeArray
			((\hsc_ptr -> hsc_ptr `plusPtr` 56) p) $ take 2 os |]) ]
{-# LINE 283 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

struct "Blit2" (96) 8 [
{-# LINE 286 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p
{-# LINE 288 "src/Gpu/Vulkan/Image/Core.hsc" #-}
			(1000337008 ::
{-# LINE 289 "src/Gpu/Vulkan/Image/Core.hsc" #-}
				Word32) |]),
{-# LINE 290 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 292 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 293 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcSubresource", ''SubresourceLayers,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 295 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 296 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("srcOffsets", ''ListOffset3d,
		[| \p -> peekArray 2  ((\hsc_ptr -> hsc_ptr `plusPtr` 32) p) |],
{-# LINE 298 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| \p os -> pokeArray
			((\hsc_ptr -> hsc_ptr `plusPtr` 32) p) $ take 2 os |]),
{-# LINE 300 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstSubresource", ''SubresourceLayers,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 56) |],
{-# LINE 302 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 56) |]),
{-# LINE 303 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("dstOffsets", ''ListOffset3d,
		[| \p -> peekArray 2 ((\hsc_ptr -> hsc_ptr `plusPtr` 72) p) |],
{-# LINE 305 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| \p os -> pokeArray
			((\hsc_ptr -> hsc_ptr `plusPtr` 72) p) $ take 2 os |]) ]
{-# LINE 307 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]

type PtrBlit2 = Ptr Blit2

struct "Subresource" (12)
{-# LINE 312 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	4 [
{-# LINE 313 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("aspectMask", ''Word32,
{-# LINE 314 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 315 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 316 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("mipLevel", ''Word32,
{-# LINE 317 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 318 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 319 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	("arrayLayer", ''Word32,
{-# LINE 320 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 321 "src/Gpu/Vulkan/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 322 "src/Gpu/Vulkan/Image/Core.hsc" #-}
	[''Show, ''Storable]