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

module Gpu.Vulkan.Sparse.Core where

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

import Gpu.Vulkan.Memory.Core qualified as Memory



struct "MemoryBind" (40) 8 [
{-# LINE 19 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	("resourceOffset", ''Word64,
{-# LINE 20 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 21 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 22 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	("size", ''Word64,
{-# LINE 23 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 24 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 25 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	("memory", ''Memory.M,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 27 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 28 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	("memoryOffset", ''Word64,
{-# LINE 29 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 30 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 31 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 32 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 33 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]) ]
{-# LINE 34 "src/Gpu/Vulkan/Sparse/Core.hsc" #-}
	[''Show, ''Storable]

type PtrMemoryBind = Ptr MemoryBind