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

module Gpu.Vulkan.QueueFamily.Core (

	-- * PROPERTIES

	Properties, pattern Properties,
	propertiesQueueFlags, propertiesQueueCount,
	propertiesTimestampValidBits, propertiesMinImageTransferGranularity

	) where

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



import Gpu.Vulkan.Core

struct "Properties" (24)
{-# LINE 25 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		4 [
{-# LINE 26 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
	("queueFlags", ''Word32,
{-# LINE 27 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 28 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 29 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
	("queueCount", ''Word32,
{-# LINE 30 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 31 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 32 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
	("timestampValidBits", ''Word32,
{-# LINE 33 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 34 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 35 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
	("minImageTransferGranularity", ''Extent3d,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 38 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]) ]
{-# LINE 40 "src/Gpu/Vulkan/QueueFamily/Core.hsc" #-}
	[''Show, ''Storable]