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

module Gpu.Vulkan.Sparse.Image.Core where

import Foreign.Ptr
import Foreign.Storable
import Foreign.C.Struct
import Data.Word

import Gpu.Vulkan.Core
import Gpu.Vulkan.Memory.Core qualified as Memory
import Gpu.Vulkan.Image.Core qualified as Image
import Gpu.Vulkan.Sparse.Core qualified as S



struct "OpaqueMemoryBindInfo" (24)
{-# LINE 22 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	8 [
{-# LINE 23 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("image", ''Image.I,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 25 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 26 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("bindCount", ''Word32,
{-# LINE 27 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 28 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 29 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("pBinds", ''S.PtrMemoryBind,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 31 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]) ]
{-# LINE 32 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	[''Show, ''Storable]

type PtrOpaqueMemoryBindInfo = Ptr OpaqueMemoryBindInfo

struct "MemoryBind" (64)
{-# LINE 37 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	8 [
{-# LINE 38 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("subresource", ''Image.Subresource,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 40 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 41 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("offset", ''Offset3d,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 43 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]),
{-# LINE 44 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("extent", ''Extent3d,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 46 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 47 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("memory", ''Memory.M,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 49 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 50 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("memoryOffset", ''Word64,
{-# LINE 51 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 52 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]),
{-# LINE 53 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 54 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 56) |],
{-# LINE 55 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 56) |]) ]
{-# LINE 56 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	[''Show, ''Storable]

type PtrMemoryBind = Ptr MemoryBind

struct "MemoryBindInfo" (24)
{-# LINE 61 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	8 [
{-# LINE 62 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("image", ''Image.I,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 64 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 65 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("bindCount", ''Word32,
{-# LINE 66 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 67 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 68 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	("pBinds", ''PtrMemoryBind,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 70 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]) ]
{-# LINE 71 "src/Gpu/Vulkan/Sparse/Image/Core.hsc" #-}
	[''Show, ''Storable]

type PtrMemoryBindInfo = Ptr MemoryBindInfo