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

module Gpu.Vulkan.BufferView.Core (

	-- * CREATE AND DESTROY

	create, destroy, B, PtrB,
	CreateInfo, pattern CreateInfo,
	createInfoSType, createInfoPNext, createInfoFlags,
	createInfoBuffer, createInfoFormat, createInfoOffset, createInfoRange

	) where

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

import qualified Gpu.Vulkan.AllocationCallbacks.Core as AllocationCallbacks
import qualified Gpu.Vulkan.Device.Core as Device
import qualified Gpu.Vulkan.Buffer.Core as Buffer



stype :: Word32
{-# LINE 31 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
stype = 13
{-# LINE 32 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}

struct "CreateInfo" (56)
{-# LINE 34 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		8 [
{-# LINE 35 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p stype |]),
{-# LINE 37 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 39 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 40 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 41 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 42 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 43 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("buffer", ''Buffer.B,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 45 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 46 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("format", ''Word32,
{-# LINE 47 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 48 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]),
{-# LINE 49 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("offset", ''Word64,
{-# LINE 50 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 51 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 52 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	("range", ''Word64,
{-# LINE 53 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 54 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]) ]
{-# LINE 55 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}
	[''Show, ''Storable]

data BTag
type B = Ptr BTag

type PtrB = Ptr B

foreign import ccall "vkCreateBufferView" create ::
	Device.D -> Ptr CreateInfo -> Ptr AllocationCallbacks.A -> PtrB ->
	IO Int32
{-# LINE 65 "src/Gpu/Vulkan/BufferView/Core.hsc" #-}

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