{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
module Gpu.Vulkan.Sampler (
create, S, pattern Null, M.CreateInfo(..),
module Gpu.Vulkan.Sampler.Enum
) where
import Foreign.Storable.PeekPoke
import Control.Exception
import Data.TypeLevel.Maybe qualified as TMaybe
import Data.TypeLevel.ParMaybe qualified as TPMaybe
import Data.TypeLevel.Tuple.Uncurry
import qualified Gpu.Vulkan.AllocationCallbacks as AllocationCallbacks
import qualified Gpu.Vulkan.AllocationCallbacks.Type as AllocationCallbacks
import qualified Gpu.Vulkan.Device.Type as Device
import qualified Gpu.Vulkan.Sampler.Middle as M
import Gpu.Vulkan.Sampler.Enum
import Gpu.Vulkan.Sampler.Type
create :: (WithPoked (TMaybe.M mn), AllocationCallbacks.ToMiddle mac) =>
Device.D sd -> M.CreateInfo mn ->
TPMaybe.M (U2 AllocationCallbacks.A) mac ->
(forall s . S s -> IO a) -> IO a
create :: forall (mn :: Maybe (*)) (mac :: Maybe (*, *)) sd a.
(WithPoked (M mn), ToMiddle mac) =>
D sd
-> CreateInfo mn -> M (U2 A) mac -> (forall s. S s -> IO a) -> IO a
create (Device.D D
dvc) CreateInfo mn
ci
(M (U2 A) mac -> M A (Snd mac)
forall (msa :: Maybe (*, *)).
ToMiddle msa =>
M (U2 A) msa -> M A (Snd msa)
AllocationCallbacks.toMiddle -> M A (Snd mac)
mac) forall s. S s -> IO a
f =
IO S -> (S -> IO ()) -> (S -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (D -> CreateInfo mn -> M A (Snd mac) -> IO S
forall (mn :: Maybe (*)) (mc :: Maybe (*)).
WithPoked (M mn) =>
D -> CreateInfo mn -> M A mc -> IO S
M.create D
dvc CreateInfo mn
ci M A (Snd mac)
mac) (\S
s -> D -> S -> M A (Snd mac) -> IO ()
forall (md :: Maybe (*)). D -> S -> M A md -> IO ()
M.destroy D
dvc S
s M A (Snd mac)
mac) (S Any -> IO a
forall s. S s -> IO a
f (S Any -> IO a) -> (S -> S Any) -> S -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. S -> S Any
forall s. S -> S s
S)