{-# language CPP #-}
module Vulkan.Core10.Event ( createEvent
, withEvent
, destroyEvent
, getEventStatus
, setEvent
, resetEvent
, EventCreateInfo(..)
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.IO.Class (MonadIO)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCreateEvent))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyEvent))
import Vulkan.Dynamic (DeviceCmds(pVkGetEventStatus))
import Vulkan.Dynamic (DeviceCmds(pVkResetEvent))
import Vulkan.Dynamic (DeviceCmds(pVkSetEvent))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Handles (Event)
import Vulkan.Core10.Handles (Event(..))
import Vulkan.Core10.Enums.EventCreateFlags (EventCreateFlags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EVENT_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateEvent
:: FunPtr (Ptr Device_T -> Ptr EventCreateInfo -> Ptr AllocationCallbacks -> Ptr Event -> IO Result) -> Ptr Device_T -> Ptr EventCreateInfo -> Ptr AllocationCallbacks -> Ptr Event -> IO Result
createEvent :: forall io . MonadIO io => Device -> EventCreateInfo -> ("allocator" ::: Maybe AllocationCallbacks) -> io (Event)
createEvent :: Device
-> EventCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Event
createEvent device :: Device
device createInfo :: EventCreateInfo
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Event -> io Event
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Event -> io Event)
-> (ContT Event IO Event -> IO Event)
-> ContT Event IO Event
-> io Event
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Event IO Event -> IO Event
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Event IO Event -> io Event)
-> ContT Event IO Event -> io Event
forall a b. (a -> b) -> a -> b
$ do
let vkCreateEventPtr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
vkCreateEventPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
pVkCreateEvent (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT Event IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Event IO ()) -> IO () -> ContT Event IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
vkCreateEventPtr FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCreateEvent' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result
vkCreateEvent' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result
mkVkCreateEvent FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result)
vkCreateEventPtr
"pCreateInfo" ::: Ptr EventCreateInfo
pCreateInfo <- ((("pCreateInfo" ::: Ptr EventCreateInfo) -> IO Event) -> IO Event)
-> ContT Event IO ("pCreateInfo" ::: Ptr EventCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr EventCreateInfo) -> IO Event)
-> IO Event)
-> ContT Event IO ("pCreateInfo" ::: Ptr EventCreateInfo))
-> ((("pCreateInfo" ::: Ptr EventCreateInfo) -> IO Event)
-> IO Event)
-> ContT Event IO ("pCreateInfo" ::: Ptr EventCreateInfo)
forall a b. (a -> b) -> a -> b
$ EventCreateInfo
-> (("pCreateInfo" ::: Ptr EventCreateInfo) -> IO Event)
-> IO Event
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (EventCreateInfo
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Event IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Event)
-> IO Event)
-> ContT Event IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Event)
-> IO Event)
-> ContT Event IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Event)
-> IO Event)
-> ContT Event IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Event)
-> IO Event
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pEvent" ::: Ptr Event
pPEvent <- ((("pEvent" ::: Ptr Event) -> IO Event) -> IO Event)
-> ContT Event IO ("pEvent" ::: Ptr Event)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pEvent" ::: Ptr Event) -> IO Event) -> IO Event)
-> ContT Event IO ("pEvent" ::: Ptr Event))
-> ((("pEvent" ::: Ptr Event) -> IO Event) -> IO Event)
-> ContT Event IO ("pEvent" ::: Ptr Event)
forall a b. (a -> b) -> a -> b
$ IO ("pEvent" ::: Ptr Event)
-> (("pEvent" ::: Ptr Event) -> IO ())
-> (("pEvent" ::: Ptr Event) -> IO Event)
-> IO Event
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pEvent" ::: Ptr Event)
forall a. Int -> IO (Ptr a)
callocBytes @Event 8) ("pEvent" ::: Ptr Event) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT Event IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Event IO Result)
-> IO Result -> ContT Event IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pEvent" ::: Ptr Event)
-> IO Result
vkCreateEvent' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr EventCreateInfo
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pEvent" ::: Ptr Event
pPEvent)
IO () -> ContT Event IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Event IO ()) -> IO () -> ContT Event IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Event
pEvent <- IO Event -> ContT Event IO Event
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Event -> ContT Event IO Event)
-> IO Event -> ContT Event IO Event
forall a b. (a -> b) -> a -> b
$ ("pEvent" ::: Ptr Event) -> IO Event
forall a. Storable a => Ptr a -> IO a
peek @Event "pEvent" ::: Ptr Event
pPEvent
Event -> ContT Event IO Event
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Event -> ContT Event IO Event) -> Event -> ContT Event IO Event
forall a b. (a -> b) -> a -> b
$ (Event
pEvent)
withEvent :: forall io r . MonadIO io => Device -> EventCreateInfo -> Maybe AllocationCallbacks -> (io (Event) -> ((Event) -> io ()) -> r) -> r
withEvent :: Device
-> EventCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Event -> (Event -> io ()) -> r)
-> r
withEvent device :: Device
device pCreateInfo :: EventCreateInfo
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io Event -> (Event -> io ()) -> r
b =
io Event -> (Event -> io ()) -> r
b (Device
-> EventCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Event
forall (io :: * -> *).
MonadIO io =>
Device
-> EventCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Event
createEvent Device
device EventCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(Event
o0) -> Device
-> Event -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Event -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyEvent Device
device Event
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkDestroyEvent
:: FunPtr (Ptr Device_T -> Event -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> Event -> Ptr AllocationCallbacks -> IO ()
destroyEvent :: forall io . MonadIO io => Device -> Event -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyEvent :: Device
-> Event -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyEvent device :: Device
device event :: Event
event allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkDestroyEventPtr :: FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyEventPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyEvent (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyEventPtr FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkDestroyEvent' :: Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyEvent' = FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Device_T
-> Event
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyEvent FunPtr
(Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyEventPtr
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Event -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyEvent' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Event
event) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetEventStatus
:: FunPtr (Ptr Device_T -> Event -> IO Result) -> Ptr Device_T -> Event -> IO Result
getEventStatus :: forall io . MonadIO io => Device -> Event -> io (Result)
getEventStatus :: Device -> Event -> io Result
getEventStatus device :: Device
device event :: Event
event = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result) -> IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
let vkGetEventStatusPtr :: FunPtr (Ptr Device_T -> Event -> IO Result)
vkGetEventStatusPtr = DeviceCmds -> FunPtr (Ptr Device_T -> Event -> IO Result)
pVkGetEventStatus (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> Event -> IO Result)
vkGetEventStatusPtr FunPtr (Ptr Device_T -> Event -> IO Result)
-> FunPtr (Ptr Device_T -> Event -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> Event -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetEventStatus is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetEventStatus' :: Ptr Device_T -> Event -> IO Result
vkGetEventStatus' = FunPtr (Ptr Device_T -> Event -> IO Result)
-> Ptr Device_T -> Event -> IO Result
mkVkGetEventStatus FunPtr (Ptr Device_T -> Event -> IO Result)
vkGetEventStatusPtr
Result
r <- Ptr Device_T -> Event -> IO Result
vkGetEventStatus' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Event
event)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
Result -> IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkSetEvent
:: FunPtr (Ptr Device_T -> Event -> IO Result) -> Ptr Device_T -> Event -> IO Result
setEvent :: forall io . MonadIO io => Device -> Event -> io ()
setEvent :: Device -> Event -> io ()
setEvent device :: Device
device event :: Event
event = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkSetEventPtr :: FunPtr (Ptr Device_T -> Event -> IO Result)
vkSetEventPtr = DeviceCmds -> FunPtr (Ptr Device_T -> Event -> IO Result)
pVkSetEvent (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> Event -> IO Result)
vkSetEventPtr FunPtr (Ptr Device_T -> Event -> IO Result)
-> FunPtr (Ptr Device_T -> Event -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> Event -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkSetEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkSetEvent' :: Ptr Device_T -> Event -> IO Result
vkSetEvent' = FunPtr (Ptr Device_T -> Event -> IO Result)
-> Ptr Device_T -> Event -> IO Result
mkVkSetEvent FunPtr (Ptr Device_T -> Event -> IO Result)
vkSetEventPtr
Result
r <- Ptr Device_T -> Event -> IO Result
vkSetEvent' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Event
event)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkResetEvent
:: FunPtr (Ptr Device_T -> Event -> IO Result) -> Ptr Device_T -> Event -> IO Result
resetEvent :: forall io . MonadIO io => Device -> Event -> io ()
resetEvent :: Device -> Event -> io ()
resetEvent device :: Device
device event :: Event
event = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkResetEventPtr :: FunPtr (Ptr Device_T -> Event -> IO Result)
vkResetEventPtr = DeviceCmds -> FunPtr (Ptr Device_T -> Event -> IO Result)
pVkResetEvent (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> Event -> IO Result)
vkResetEventPtr FunPtr (Ptr Device_T -> Event -> IO Result)
-> FunPtr (Ptr Device_T -> Event -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> Event -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkResetEvent is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkResetEvent' :: Ptr Device_T -> Event -> IO Result
vkResetEvent' = FunPtr (Ptr Device_T -> Event -> IO Result)
-> Ptr Device_T -> Event -> IO Result
mkVkResetEvent FunPtr (Ptr Device_T -> Event -> IO Result)
vkResetEventPtr
Result
r <- Ptr Device_T -> Event -> IO Result
vkResetEvent' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Event
event)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data EventCreateInfo = EventCreateInfo
{
EventCreateInfo -> EventCreateFlags
flags :: EventCreateFlags }
deriving (Typeable)
deriving instance Show EventCreateInfo
instance ToCStruct EventCreateInfo where
withCStruct :: EventCreateInfo
-> (("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b) -> IO b
withCStruct x :: EventCreateInfo
x f :: ("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b
f = Int
-> Int -> (("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b) -> IO b)
-> (("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pCreateInfo" ::: Ptr EventCreateInfo
p -> ("pCreateInfo" ::: Ptr EventCreateInfo)
-> EventCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr EventCreateInfo
p EventCreateInfo
x (("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b
f "pCreateInfo" ::: Ptr EventCreateInfo
p)
pokeCStruct :: ("pCreateInfo" ::: Ptr EventCreateInfo)
-> EventCreateInfo -> IO b -> IO b
pokeCStruct p :: "pCreateInfo" ::: Ptr EventCreateInfo
p EventCreateInfo{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EVENT_CREATE_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr EventCreateFlags -> EventCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo)
-> Int -> Ptr EventCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr EventCreateFlags)) (EventCreateFlags
flags)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pCreateInfo" ::: Ptr EventCreateInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pCreateInfo" ::: Ptr EventCreateInfo
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EVENT_CREATE_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct EventCreateInfo where
peekCStruct :: ("pCreateInfo" ::: Ptr EventCreateInfo) -> IO EventCreateInfo
peekCStruct p :: "pCreateInfo" ::: Ptr EventCreateInfo
p = do
EventCreateFlags
flags <- Ptr EventCreateFlags -> IO EventCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @EventCreateFlags (("pCreateInfo" ::: Ptr EventCreateInfo
p ("pCreateInfo" ::: Ptr EventCreateInfo)
-> Int -> Ptr EventCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr EventCreateFlags))
EventCreateInfo -> IO EventCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EventCreateInfo -> IO EventCreateInfo)
-> EventCreateInfo -> IO EventCreateInfo
forall a b. (a -> b) -> a -> b
$ EventCreateFlags -> EventCreateInfo
EventCreateInfo
EventCreateFlags
flags
instance Storable EventCreateInfo where
sizeOf :: EventCreateInfo -> Int
sizeOf ~EventCreateInfo
_ = 24
alignment :: EventCreateInfo -> Int
alignment ~EventCreateInfo
_ = 8
peek :: ("pCreateInfo" ::: Ptr EventCreateInfo) -> IO EventCreateInfo
peek = ("pCreateInfo" ::: Ptr EventCreateInfo) -> IO EventCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCreateInfo" ::: Ptr EventCreateInfo) -> EventCreateInfo -> IO ()
poke ptr :: "pCreateInfo" ::: Ptr EventCreateInfo
ptr poked :: EventCreateInfo
poked = ("pCreateInfo" ::: Ptr EventCreateInfo)
-> EventCreateInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr EventCreateInfo
ptr EventCreateInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero EventCreateInfo where
zero :: EventCreateInfo
zero = EventCreateFlags -> EventCreateInfo
EventCreateInfo
EventCreateFlags
forall a. Zero a => a
zero