{-# LINE 1 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
module Gpu.Vulkan.Base.Middle.Internal (
boolToBool32, bool32ToBool,
pattern NullHandle,
ObjectHandle(..)
) where
import Foreign.Ptr
import Data.Word
boolToBool32 :: Bool -> Word32
{-# LINE 26 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
boolToBool32 False = 0
{-# LINE 27 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
boolToBool32 True = 1
{-# LINE 28 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
bool32ToBool :: Word32 -> Bool
{-# LINE 30 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
bool32ToBool 0 = False
{-# LINE 31 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
bool32ToBool 1 = True
{-# LINE 32 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
bool32ToBool _ = error $
"Application must not pass any other values than " ++
"VK_TRUE or VK_FALSE into a Gpu.Vulkan implementation " ++
"where a VkBool32 is expected"
newtype ObjectHandle = ObjectHandle Word64 deriving Int -> ObjectHandle -> [Char] -> [Char]
[ObjectHandle] -> [Char] -> [Char]
ObjectHandle -> [Char]
(Int -> ObjectHandle -> [Char] -> [Char])
-> (ObjectHandle -> [Char])
-> ([ObjectHandle] -> [Char] -> [Char])
-> Show ObjectHandle
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> ObjectHandle -> [Char] -> [Char]
showsPrec :: Int -> ObjectHandle -> [Char] -> [Char]
$cshow :: ObjectHandle -> [Char]
show :: ObjectHandle -> [Char]
$cshowList :: [ObjectHandle] -> [Char] -> [Char]
showList :: [ObjectHandle] -> [Char] -> [Char]
Show
{-# LINE 38 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
pattern NullHandle :: Ptr a
pattern $mNullHandle :: forall {r} {a}. Ptr a -> ((# #) -> r) -> ((# #) -> r) -> r
$bNullHandle :: forall a. Ptr a
NullHandle <- (ptrToWordPtr -> (WordPtr 0)) where
{-# LINE 41 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}
NullHandle = WordPtr -> Ptr a
forall a. WordPtr -> Ptr a
wordPtrToPtr (WordPtr -> Ptr a) -> WordPtr -> Ptr a
forall a b. (a -> b) -> a -> b
$ Word -> WordPtr
WordPtr Word
0
{-# LINE 42 "src/Gpu/Vulkan/Base/Middle/Internal.hsc" #-}