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

module Gpu.Vulkan.Core (

	-- * INFO

	-- ** ApplicationInfo

	ApplicationInfo, PtrApplicationInfo, pattern ApplicationInfo,
	applicationInfoSType, applicationInfoPNext,
	applicationInfoPApplicationName, applicationInfoApplicationVersion,
	applicationInfoPEngineName, applicationInfoEngineVersion,
	applicationInfoApiVersion,

	-- *** ApiVersion

	ApiVersion, makeApiVersion, apiVersion_1_0, apiVersion_1_1,

	-- ** SubmitInfo

	SubmitInfo, pattern SubmitInfo,
	submitInfoSType, submitInfoPNext,
	submitInfoWaitSemaphoreCount, submitInfoPWaitSemaphores,
	submitInfoPWaitDstStageMask, PtrPipelineStageFlags,
	submitInfoCommandBufferCount, submitInfoPCommandBuffers,
	submitInfoSignalSemaphoreCount, submitInfoPSignalSemaphores,

	-- * PROPERTIES

	-- ** ExtensionProperties

	ExtensionProperties, pattern ExtensionProperties,
	extensionPropertiesExtensionName, extensionPropertiesSpecVersion,

	-- ** LayerProperties

	LayerProperties, pattern LayerProperties,
	layerPropertiesLayerName, layerPropertiesSpecVersion,
	layerPropertiesImplementationVersion, layerPropertiesDescription,

	-- ** FormatProperties

	FormatProperties, pattern FormatProperties,
	formatPropertiesLinearTilingFeatures,
	formatPropertiesOptimalTilingFeatures, formatPropertiesBufferFeatures,

	-- * PIPELINE VALUES

	-- ** Viewport

	Viewport, PtrViewport, pattern Viewport,
	viewportX, viewportY, viewportWidth, viewportHeight,
	viewportMinDepth, viewportMaxDepth,

	-- ** StencilOpState

	StencilOpState, pattern StencilOpState,
	stencilOpStateFailOp, stencilOpStatePassOp, stencilOpStateDepthFailOp,
	stencilOpStateCompareOp, stencilOpStateCompareMask,
	stencilOpStateWriteMask, stencilOpStateReference,

	-- ** ClearValue

	ClearValue, PtrClearValue,
	clearValueFromClearColorValue, clearValueFromClearDepthStencilValue,

	-- *** ClearColorValue

	ClearColorValue,
	clearColorValueFromUints, clearColorValueFromInts,
	clearColorValueFromFloats,

	-- *** ClearDepthStencilValue
	
	ClearDepthStencilValue, pattern ClearDepthStencilValue,
	clearDepthStencilValueDepth, clearDepthStencilValueStencil,

	-- * STRUCT COMMON

	StructCommon, pattern StructCommon,
	structCommonSType, structCommonPNext,

	-- * RECT, OFFSET AND EXTENT

	-- ** Rect

	Rect2d, PtrRect2d, pattern Rect2d,
	rect2dExtent, rect2dOffset,

	-- ** Offset

	Offset2d, pattern Offset2d,
	offset2dX, offset2dY,

	Offset3d, ListOffset3d, pattern Offset3d,
	offset3dX, offset3dY, offset3dZ,

	-- ** Extent

	Extent2d, pattern Extent2d,
	extent2dWidth, extent2dHeight,

	Extent3d, pattern Extent3d,
	extent3dWidth, extent3dHeight, extent3dDepth,

	) where

import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Marshal.Utils
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String
import Foreign.C.Struct
import Foreign.C.Struct.TypeSynonyms
import Data.Word
import Data.Int

import qualified Data.Text as Txt
import qualified Data.Text.Foreign as Txt

import {-# SOURCE #-} qualified Gpu.Vulkan.CommandBuffer.Core as CommandBuffer
import {-# SOURCE #-} qualified Gpu.Vulkan.Semaphore.Core as Semaphore



struct "StructCommon" (48)
{-# LINE 133 "src/Gpu/Vulkan/Core.hsc" #-}
		8 [
{-# LINE 134 "src/Gpu/Vulkan/Core.hsc" #-}
	("sType", ''Word32,
{-# LINE 135 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 136 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |] ),
{-# LINE 137 "src/Gpu/Vulkan/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 139 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 140 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

type ApiVersion = Word32
{-# LINE 143 "src/Gpu/Vulkan/Core.hsc" #-}

struct "ApplicationInfo" (48)
{-# LINE 145 "src/Gpu/Vulkan/Core.hsc" #-}
		8 [
{-# LINE 146 "src/Gpu/Vulkan/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p
{-# LINE 148 "src/Gpu/Vulkan/Core.hsc" #-}
			(0 ::
{-# LINE 149 "src/Gpu/Vulkan/Core.hsc" #-}
				Word32) |]),
{-# LINE 150 "src/Gpu/Vulkan/Core.hsc" #-}
	("pNext", ''PtrVoid, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 151 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 152 "src/Gpu/Vulkan/Core.hsc" #-}
	("pApplicationName", ''CString,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 154 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 155 "src/Gpu/Vulkan/Core.hsc" #-}
	("applicationVersion", ''ApiVersion,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 157 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 158 "src/Gpu/Vulkan/Core.hsc" #-}
	("pEngineName", ''CString,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 160 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]),
{-# LINE 161 "src/Gpu/Vulkan/Core.hsc" #-}
	("engineVersion", ''ApiVersion,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 163 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 164 "src/Gpu/Vulkan/Core.hsc" #-}
	("apiVersion", ''ApiVersion,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 44) |],
{-# LINE 166 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 44) |]) ]
{-# LINE 167 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

foreign import capi "vulkan/vulkan.h VK_MAKE_API_VERSION" makeApiVersion ::
	Word8 -> Word8 -> Word16 -> Word16 -> ApiVersion

foreign import capi "vulkan/vulkan.h value VK_API_VERSION_1_0" apiVersion_1_0 ::
	ApiVersion

foreign import capi "vulkan/vulkan.h value VK_API_VERSION_1_1" apiVersion_1_1 ::
	ApiVersion

type PtrApplicationInfo = Ptr ApplicationInfo

struct "Extent2d" (8) 4 [
{-# LINE 181 "src/Gpu/Vulkan/Core.hsc" #-}
	("width", ''Word32, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 182 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 183 "src/Gpu/Vulkan/Core.hsc" #-}
	("height", ''Word32, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 184 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]) ]
{-# LINE 185 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

struct "Extent3d" (12) 4 [
{-# LINE 188 "src/Gpu/Vulkan/Core.hsc" #-}
	("width", ''Word32, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 189 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 190 "src/Gpu/Vulkan/Core.hsc" #-}
	("height", ''Word32, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 191 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 192 "src/Gpu/Vulkan/Core.hsc" #-}
	("depth", ''Word32, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 193 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 194 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

struct "Viewport" (24) 4 [
{-# LINE 197 "src/Gpu/Vulkan/Core.hsc" #-}
	("x", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 198 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 199 "src/Gpu/Vulkan/Core.hsc" #-}
	("y", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 200 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 201 "src/Gpu/Vulkan/Core.hsc" #-}
	("width", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 202 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 203 "src/Gpu/Vulkan/Core.hsc" #-}
	("height", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 204 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]),
{-# LINE 205 "src/Gpu/Vulkan/Core.hsc" #-}
	("minDepth", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 206 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 207 "src/Gpu/Vulkan/Core.hsc" #-}
	("maxDepth", ''Float, [| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 208 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]) ]
{-# LINE 209 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

type PtrViewport = Ptr Viewport

struct "Offset2d" (8) 4 [
{-# LINE 214 "src/Gpu/Vulkan/Core.hsc" #-}
	("x", ''Int32, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 215 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 216 "src/Gpu/Vulkan/Core.hsc" #-}
	("y", ''Int32, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 217 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]) ]
{-# LINE 218 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

struct "Offset3d" (12) 4 [
{-# LINE 221 "src/Gpu/Vulkan/Core.hsc" #-}
	("x", ''Int32, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 222 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 223 "src/Gpu/Vulkan/Core.hsc" #-}
	("y", ''Int32, [| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 224 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 225 "src/Gpu/Vulkan/Core.hsc" #-}
	("z", ''Int32, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 226 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 227 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

type ListOffset3d = [Offset3d]

struct "Rect2d" (16) 4 [
{-# LINE 232 "src/Gpu/Vulkan/Core.hsc" #-}
	("offset", ''Offset2d, [| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 233 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 234 "src/Gpu/Vulkan/Core.hsc" #-}
	("extent", ''Extent2d, [| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 235 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 236 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

type PtrRect2d = Ptr Rect2d

type PtrPipelineStageFlags = Ptr Word32
{-# LINE 241 "src/Gpu/Vulkan/Core.hsc" #-}

sTypeS :: Word32
{-# LINE 243 "src/Gpu/Vulkan/Core.hsc" #-}
sTypeS = 4
{-# LINE 244 "src/Gpu/Vulkan/Core.hsc" #-}

struct "SubmitInfo" (72) 8 [
{-# LINE 246 "src/Gpu/Vulkan/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p sTypeS |]),
{-# LINE 248 "src/Gpu/Vulkan/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 250 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 251 "src/Gpu/Vulkan/Core.hsc" #-}
	("waitSemaphoreCount", ''Word32,
{-# LINE 252 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 253 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 254 "src/Gpu/Vulkan/Core.hsc" #-}
	("pWaitSemaphores", ''Semaphore.PtrS,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 256 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]),
{-# LINE 257 "src/Gpu/Vulkan/Core.hsc" #-}
	("pWaitDstStageMask", ''PtrPipelineStageFlags,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 32) |],
{-# LINE 259 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 32) |]),
{-# LINE 260 "src/Gpu/Vulkan/Core.hsc" #-}
	("commandBufferCount", ''Word32,
{-# LINE 261 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 40) |],
{-# LINE 262 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 40) |]),
{-# LINE 263 "src/Gpu/Vulkan/Core.hsc" #-}
	("pCommandBuffers", ''CommandBuffer.PtrC,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 48) |],
{-# LINE 265 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 48) |]),
{-# LINE 266 "src/Gpu/Vulkan/Core.hsc" #-}
	("signalSemaphoreCount", ''Int32,
{-# LINE 267 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 56) |],
{-# LINE 268 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 56) |]),
{-# LINE 269 "src/Gpu/Vulkan/Core.hsc" #-}
	("pSignalSemaphores", ''Semaphore.PtrS,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 64) |],
{-# LINE 271 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 64) |]) ]
{-# LINE 272 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

struct "ExtensionProperties" (260)
{-# LINE 275 "src/Gpu/Vulkan/Core.hsc" #-}
		4 [
{-# LINE 276 "src/Gpu/Vulkan/Core.hsc" #-}
	("extensionName", ''Txt.Text,
		[| \p -> Txt.takeWhile (/= '\NUL') <$> Txt.peekCStringLen
			((\hsc_ptr -> hsc_ptr `plusPtr` 0) p,
{-# LINE 279 "src/Gpu/Vulkan/Core.hsc" #-}
				256) |],
{-# LINE 280 "src/Gpu/Vulkan/Core.hsc" #-}
		[| \p bs -> Txt.withCStringLen bs \(cs, ln) -> do
			copyBytes ((\hsc_ptr -> hsc_ptr `plusPtr` 0) p) cs ln
{-# LINE 282 "src/Gpu/Vulkan/Core.hsc" #-}
			poke ((\hsc_ptr -> hsc_ptr `plusPtr` 0) p `plusPtr` ln :: Ptr CChar) 0
{-# LINE 283 "src/Gpu/Vulkan/Core.hsc" #-}
			|]
		),
	("specVersion", ''Word32,
{-# LINE 286 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 256) |],
{-# LINE 287 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 256) |]) ]
{-# LINE 288 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

struct "LayerProperties" (520)
{-# LINE 291 "src/Gpu/Vulkan/Core.hsc" #-}
		4 [
{-# LINE 292 "src/Gpu/Vulkan/Core.hsc" #-}
	("layerName", ''Txt.Text,
		[| \p -> Txt.takeWhile (/= '\NUL') <$> Txt.peekCStringLen
			((\hsc_ptr -> hsc_ptr `plusPtr` 0) p,
{-# LINE 295 "src/Gpu/Vulkan/Core.hsc" #-}
				256) |],
{-# LINE 296 "src/Gpu/Vulkan/Core.hsc" #-}
		[| \p bs -> Txt.withCStringLen bs \(cs, ln) -> do
			copyBytes ((\hsc_ptr -> hsc_ptr `plusPtr` 0) p) cs ln
{-# LINE 298 "src/Gpu/Vulkan/Core.hsc" #-}
			poke ((\hsc_ptr -> hsc_ptr `plusPtr` 0) p `plusPtr` ln :: Ptr CChar) 0
{-# LINE 299 "src/Gpu/Vulkan/Core.hsc" #-}
			|]),
	("specVersion", ''Word32,
{-# LINE 301 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 256) |],
{-# LINE 302 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 256) |]),
{-# LINE 303 "src/Gpu/Vulkan/Core.hsc" #-}
	("implementationVersion", ''Word32,
{-# LINE 304 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 260) |],
{-# LINE 305 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 260) |]),
{-# LINE 306 "src/Gpu/Vulkan/Core.hsc" #-}
	("description", ''Txt.Text,
		[| \p -> Txt.takeWhile (/= '\NUL') <$> Txt.peekCStringLen
			((\hsc_ptr -> hsc_ptr `plusPtr` 264) p,
{-# LINE 309 "src/Gpu/Vulkan/Core.hsc" #-}
				256) |],
{-# LINE 310 "src/Gpu/Vulkan/Core.hsc" #-}
		[| \p bs -> Txt.withCStringLen bs \(cs, ln) -> do
			copyBytes ((\hsc_ptr -> hsc_ptr `plusPtr` 264) p) cs ln
{-# LINE 312 "src/Gpu/Vulkan/Core.hsc" #-}
			poke ((\hsc_ptr -> hsc_ptr `plusPtr` 264) p `plusPtr` ln :: Ptr CChar) 0
{-# LINE 313 "src/Gpu/Vulkan/Core.hsc" #-}
			|]) ]
	[''Show, ''Storable]

struct "StencilOpState" (28) 4 [
{-# LINE 317 "src/Gpu/Vulkan/Core.hsc" #-}
	("failOp", ''Word32,
{-# LINE 318 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 319 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 320 "src/Gpu/Vulkan/Core.hsc" #-}
	("passOp", ''Word32,
{-# LINE 321 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 322 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 323 "src/Gpu/Vulkan/Core.hsc" #-}
	("depthFailOp", ''Word32,
{-# LINE 324 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 325 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 326 "src/Gpu/Vulkan/Core.hsc" #-}
	("compareOp", ''Word32,
{-# LINE 327 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 12) |],
{-# LINE 328 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 12) |]),
{-# LINE 329 "src/Gpu/Vulkan/Core.hsc" #-}
	("compareMask", ''Word32,
{-# LINE 330 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 331 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]),
{-# LINE 332 "src/Gpu/Vulkan/Core.hsc" #-}
	("writeMask", ''Word32,
{-# LINE 333 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 20) |],
{-# LINE 334 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 20) |]),
{-# LINE 335 "src/Gpu/Vulkan/Core.hsc" #-}
	("reference", ''Word32,
{-# LINE 336 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 24) |],
{-# LINE 337 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 24) |]) ]
{-# LINE 338 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

data ClearValue
type PtrClearValue = Ptr ClearValue
data ClearColorValue

clearColorValueFromFloats :: Ptr Float -> Ptr ClearColorValue
{-# LINE 345 "src/Gpu/Vulkan/Core.hsc" #-}
clearColorValueFromFloats = castPtr

clearColorValueFromInts :: Ptr Int32 -> Ptr ClearColorValue
{-# LINE 348 "src/Gpu/Vulkan/Core.hsc" #-}
clearColorValueFromInts = castPtr

clearColorValueFromUints :: Ptr Word32 -> Ptr ClearColorValue
{-# LINE 351 "src/Gpu/Vulkan/Core.hsc" #-}
clearColorValueFromUints = castPtr

struct "ClearDepthStencilValue" (8)
{-# LINE 354 "src/Gpu/Vulkan/Core.hsc" #-}
		4 [
{-# LINE 355 "src/Gpu/Vulkan/Core.hsc" #-}
	("depth", ''Float,
{-# LINE 356 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 357 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 358 "src/Gpu/Vulkan/Core.hsc" #-}
	("stencil", ''Word32,
{-# LINE 359 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 360 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]) ]
{-# LINE 361 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]

clearValueFromClearColorValue :: Ptr ClearColorValue -> Ptr ClearValue
clearValueFromClearColorValue :: Ptr ClearColorValue -> Ptr ClearValue
clearValueFromClearColorValue = Ptr ClearColorValue -> Ptr ClearValue
forall a b. Ptr a -> Ptr b
castPtr

clearValueFromClearDepthStencilValue ::
	ClearDepthStencilValue -> (Ptr ClearValue -> IO a) -> IO a
clearValueFromClearDepthStencilValue :: forall a.
ClearDepthStencilValue -> (Ptr ClearValue -> IO a) -> IO a
clearValueFromClearDepthStencilValue (ClearDepthStencilValue_ ForeignPtr ClearDepthStencilValue
fp) Ptr ClearValue -> IO a
f =
	ForeignPtr ClearDepthStencilValue
-> (Ptr ClearDepthStencilValue -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr ClearDepthStencilValue
fp ((Ptr ClearDepthStencilValue -> IO a) -> IO a)
-> (Ptr ClearDepthStencilValue -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ Ptr ClearValue -> IO a
f (Ptr ClearValue -> IO a)
-> (Ptr ClearDepthStencilValue -> Ptr ClearValue)
-> Ptr ClearDepthStencilValue
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr ClearDepthStencilValue -> Ptr ClearValue
forall a b. Ptr a -> Ptr b
castPtr

struct "FormatProperties" (12)
{-# LINE 372 "src/Gpu/Vulkan/Core.hsc" #-}
		4 [
{-# LINE 373 "src/Gpu/Vulkan/Core.hsc" #-}
	("linearTilingFeatures", ''Word32,
{-# LINE 374 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 0) |],
{-# LINE 375 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 0) |]),
{-# LINE 376 "src/Gpu/Vulkan/Core.hsc" #-}
	("optimalTilingFeatures", ''Word32,
{-# LINE 377 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 4) |],
{-# LINE 378 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 4) |]),
{-# LINE 379 "src/Gpu/Vulkan/Core.hsc" #-}
	("bufferFeatures", ''Word32,
{-# LINE 380 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 381 "src/Gpu/Vulkan/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]) ]
{-# LINE 382 "src/Gpu/Vulkan/Core.hsc" #-}
	[''Show, ''Storable]