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

module Gpu.Vulkan.Pipeline.DynamicState.Core (

	-- * CREATE INFO

	CreateInfo, PtrCreateInfo, pattern CreateInfo,
	createInfoSType, createInfoPNext, createInfoFlags,
	createInfoDynamicStateCount, createInfoPDynamicStates

	) where

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



sType :: Word32
{-# LINE 25 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
sType = 27
{-# LINE 26 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}

type PtrVkDynamicState = Ptr Word32
{-# LINE 28 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}

struct "CreateInfo" (32)
{-# LINE 30 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		8 [
{-# LINE 31 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0)
{-# LINE 33 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
			p sType |]),
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 36 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 37 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 38 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 39 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 40 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
	("dynamicStateCount", ''Word32,
{-# LINE 41 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 43 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]),
{-# LINE 45 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
	("pDynamicStates", ''PtrVkDynamicState,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 47 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |])
{-# LINE 48 "src/Gpu/Vulkan/Pipeline/DynamicState/Core.hsc" #-}
	]
	[''Show, ''Storable]

type PtrCreateInfo = Ptr CreateInfo