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

module Gpu.Vulkan.Fence.Core (

	-- * CREATE AND DESTROY

	create, destroy, F, CreateInfo, pattern CreateInfo,
	createInfoSType, createInfoPNext, createInfoFlags,

	-- * WAIT AND RESET

	waitForFs, resetFs

	) 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



sType :: Word32
{-# LINE 32 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
sType = 8
{-# LINE 33 "src/Gpu/Vulkan/Fence/Core.hsc" #-}

struct "CreateInfo" (24) 8 [
{-# LINE 35 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
	("sType", ''(), [| const $ pure () |],
		[| \p _ -> (\hsc_ptr -> pokeByteOff hsc_ptr 0) p sType |]),
{-# LINE 37 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
	("pNext", ''PtrVoid,
		[| (\hsc_ptr -> peekByteOff hsc_ptr 8) |],
{-# LINE 39 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 8) |]),
{-# LINE 40 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
	("flags", ''Word32,
{-# LINE 41 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
		[| (\hsc_ptr -> peekByteOff hsc_ptr 16) |],
{-# LINE 42 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
		[| (\hsc_ptr -> pokeByteOff hsc_ptr 16) |]) ]
{-# LINE 43 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
	[''Show, ''Storable]

data FTag
type F = Ptr FTag

foreign import ccall "vkCreateFence" create ::
	Device.D -> Ptr CreateInfo -> Ptr AllocationCallbacks.A -> Ptr F ->
	IO Int32
{-# LINE 51 "src/Gpu/Vulkan/Fence/Core.hsc" #-}

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

foreign import ccall "vkWaitForFences" waitForFs ::
	Device.D -> Word32 -> Ptr F -> Word32 ->
{-# LINE 57 "src/Gpu/Vulkan/Fence/Core.hsc" #-}
	Word64 -> IO Int32
{-# LINE 58 "src/Gpu/Vulkan/Fence/Core.hsc" #-}

foreign import ccall "vkResetFences" resetFs ::
	Device.D -> Word32 -> Ptr F -> IO Int32
{-# LINE 61 "src/Gpu/Vulkan/Fence/Core.hsc" #-}