{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE PatternSynonyms #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Gpu.Vulkan.Sparse.Image.Internal where import Data.TypeLevel.Tuple.Uncurry import Data.HeteroParList (pattern (:**)) import Data.HeteroParList qualified as HPList import Gpu.Vulkan.Internal import Gpu.Vulkan.Device.Internal qualified as Device import Gpu.Vulkan.Memory.Type qualified as Memory import Gpu.Vulkan.Image.Internal qualified as Image import Gpu.Vulkan.Sparse.Internal qualified as S import Gpu.Vulkan.Sparse.Enum qualified as S import Gpu.Vulkan.Sparse.Image.Middle qualified as M data OpaqueMemoryBindInfo si inm fmt sais = OpaqueMemoryBindInfo { forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). OpaqueMemoryBindInfo si inm fmt sais -> I si inm fmt opaqueMemoryBindInfoImage :: Image.I si inm fmt, forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). OpaqueMemoryBindInfo si inm fmt sais -> PL (U3 MemoryBind) sais opaqueMemoryBindInfoBinds :: HPList.PL (U3 S.MemoryBind) sais } opaqueMemoryBindInfoToMiddle :: S.MemoryBindsToMiddle sais => Device.D sd -> OpaqueMemoryBindInfo si inm fmt sais -> IO M.OpaqueMemoryBindInfo opaqueMemoryBindInfoToMiddle :: forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd si (inm :: Symbol) (fmt :: Format). MemoryBindsToMiddle sais => D sd -> OpaqueMemoryBindInfo si inm fmt sais -> IO OpaqueMemoryBindInfo opaqueMemoryBindInfoToMiddle D sd dv OpaqueMemoryBindInfo { opaqueMemoryBindInfoImage :: forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). OpaqueMemoryBindInfo si inm fmt sais -> I si inm fmt opaqueMemoryBindInfoImage = Image.I I i, opaqueMemoryBindInfoBinds :: forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). OpaqueMemoryBindInfo si inm fmt sais -> PL (U3 MemoryBind) sais opaqueMemoryBindInfoBinds = PL (U3 MemoryBind) sais bs } = do mbs <- D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd. MemoryBindsToMiddle sais => D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] forall sd. D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] S.memoryBindsToMiddle D sd dv PL (U3 MemoryBind) sais bs pure M.OpaqueMemoryBindInfo { M.opaqueMemoryBindInfoImage = i, M.opaqueMemoryBindInfoBinds = mbs } class OpaqueMemoryBindInfosToMiddle ombias where opaqueMemoryBindInfosToMiddle :: Device.D sd -> HPList.PL (U4 OpaqueMemoryBindInfo) ombias -> IO [M.OpaqueMemoryBindInfo] instance OpaqueMemoryBindInfosToMiddle '[] where opaqueMemoryBindInfosToMiddle :: forall sd. D sd -> PL (U4 OpaqueMemoryBindInfo) '[] -> IO [OpaqueMemoryBindInfo] opaqueMemoryBindInfosToMiddle D sd _ PL (U4 OpaqueMemoryBindInfo) '[] HPList.Nil = [OpaqueMemoryBindInfo] -> IO [OpaqueMemoryBindInfo] forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure [] instance (S.MemoryBindsToMiddle sais, OpaqueMemoryBindInfosToMiddle ombias) => OpaqueMemoryBindInfosToMiddle ('(si, inm, fmt, sais) ': ombias) where opaqueMemoryBindInfosToMiddle :: forall sd. D sd -> PL (U4 OpaqueMemoryBindInfo) ('(si, inm, fmt, sais) : ombias) -> IO [OpaqueMemoryBindInfo] opaqueMemoryBindInfosToMiddle D sd dv (U4 OpaqueMemoryBindInfo s1 s2 s3 s4 ombi :** PL (U4 OpaqueMemoryBindInfo) ss1 ombis) = (:) (OpaqueMemoryBindInfo -> [OpaqueMemoryBindInfo] -> [OpaqueMemoryBindInfo]) -> IO OpaqueMemoryBindInfo -> IO ([OpaqueMemoryBindInfo] -> [OpaqueMemoryBindInfo]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> D sd -> OpaqueMemoryBindInfo s1 s2 s3 s4 -> IO OpaqueMemoryBindInfo forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd si (inm :: Symbol) (fmt :: Format). MemoryBindsToMiddle sais => D sd -> OpaqueMemoryBindInfo si inm fmt sais -> IO OpaqueMemoryBindInfo opaqueMemoryBindInfoToMiddle D sd dv OpaqueMemoryBindInfo s1 s2 s3 s4 ombi IO ([OpaqueMemoryBindInfo] -> [OpaqueMemoryBindInfo]) -> IO [OpaqueMemoryBindInfo] -> IO [OpaqueMemoryBindInfo] forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> D sd -> PL (U4 OpaqueMemoryBindInfo) ss1 -> IO [OpaqueMemoryBindInfo] forall (ombias :: [(*, Symbol, Format, [(*, [(*, ImageBufferArg)], Nat)])]) sd. OpaqueMemoryBindInfosToMiddle ombias => D sd -> PL (U4 OpaqueMemoryBindInfo) ombias -> IO [OpaqueMemoryBindInfo] forall sd. D sd -> PL (U4 OpaqueMemoryBindInfo) ss1 -> IO [OpaqueMemoryBindInfo] opaqueMemoryBindInfosToMiddle D sd dv PL (U4 OpaqueMemoryBindInfo) ss1 ombis data MemoryBindInfo si inm fmt sais = MemoryBindInfo { forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). MemoryBindInfo si inm fmt sais -> I si inm fmt memoryBindInfoImage :: Image.I si inm fmt, forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). MemoryBindInfo si inm fmt sais -> PL (U3 MemoryBind) sais memoryBindInfoBinds :: HPList.PL (U3 MemoryBind) sais } memoryBindInfoToMiddle :: MemoryBindsToMiddle sais => Device.D sd -> MemoryBindInfo si inm fmt sais -> IO M.MemoryBindInfo memoryBindInfoToMiddle :: forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd si (inm :: Symbol) (fmt :: Format). MemoryBindsToMiddle sais => D sd -> MemoryBindInfo si inm fmt sais -> IO MemoryBindInfo memoryBindInfoToMiddle D sd dv MemoryBindInfo { memoryBindInfoImage :: forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). MemoryBindInfo si inm fmt sais -> I si inm fmt memoryBindInfoImage = Image.I I mi, memoryBindInfoBinds :: forall si (inm :: Symbol) (fmt :: Format) (sais :: [(*, [(*, ImageBufferArg)], Nat)]). MemoryBindInfo si inm fmt sais -> PL (U3 MemoryBind) sais memoryBindInfoBinds = PL (U3 MemoryBind) sais bs } = do mbs <- D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd. MemoryBindsToMiddle sais => D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] forall sd. D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] memoryBindsToMiddle D sd dv PL (U3 MemoryBind) sais bs pure M.MemoryBindInfo { M.memoryBindInfoImage = mi, M.memoryBindInfoBinds = mbs } class MemoryBindInfosToMiddle mbias where memoryBindInfosToMiddle :: Device.D sd -> HPList.PL (U4 MemoryBindInfo) mbias -> IO [M.MemoryBindInfo] instance MemoryBindInfosToMiddle '[] where memoryBindInfosToMiddle :: forall sd. D sd -> PL (U4 MemoryBindInfo) '[] -> IO [MemoryBindInfo] memoryBindInfosToMiddle D sd _ PL (U4 MemoryBindInfo) '[] HPList.Nil = [MemoryBindInfo] -> IO [MemoryBindInfo] forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure [] instance (MemoryBindsToMiddle sais, MemoryBindInfosToMiddle mbias) => MemoryBindInfosToMiddle ('(si, inm, fmt, sais) ': mbias) where memoryBindInfosToMiddle :: forall sd. D sd -> PL (U4 MemoryBindInfo) ('(si, inm, fmt, sais) : mbias) -> IO [MemoryBindInfo] memoryBindInfosToMiddle D sd dv (U4 MemoryBindInfo s1 s2 s3 s4 mbi :** PL (U4 MemoryBindInfo) ss1 mbis) = (:) (MemoryBindInfo -> [MemoryBindInfo] -> [MemoryBindInfo]) -> IO MemoryBindInfo -> IO ([MemoryBindInfo] -> [MemoryBindInfo]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> D sd -> MemoryBindInfo s1 s2 s3 s4 -> IO MemoryBindInfo forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd si (inm :: Symbol) (fmt :: Format). MemoryBindsToMiddle sais => D sd -> MemoryBindInfo si inm fmt sais -> IO MemoryBindInfo memoryBindInfoToMiddle D sd dv MemoryBindInfo s1 s2 s3 s4 mbi IO ([MemoryBindInfo] -> [MemoryBindInfo]) -> IO [MemoryBindInfo] -> IO [MemoryBindInfo] forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> D sd -> PL (U4 MemoryBindInfo) ss1 -> IO [MemoryBindInfo] forall (mbias :: [(*, Symbol, Format, [(*, [(*, ImageBufferArg)], Nat)])]) sd. MemoryBindInfosToMiddle mbias => D sd -> PL (U4 MemoryBindInfo) mbias -> IO [MemoryBindInfo] forall sd. D sd -> PL (U4 MemoryBindInfo) ss1 -> IO [MemoryBindInfo] memoryBindInfosToMiddle D sd dv PL (U4 MemoryBindInfo) ss1 mbis data MemoryBind sm ibargs i = MemoryBind { forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Subresource memoryBindSubresource :: Image.Subresource, forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Offset3d memoryBindOffset :: Offset3d, forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Extent3d memoryBindExtent :: Extent3d, forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> M sm ibargs memoryBindMemory :: Memory.M sm ibargs, forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> RawOffset i memoryBindMemoryOffset :: Memory.RawOffset i, forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> MemoryBindFlags memoryBindFlags :: S.MemoryBindFlags } memoryBindToMiddle :: Memory.RawOffsetToOffset ibargs i => Device.D sd -> MemoryBind sm ibargs i -> IO M.MemoryBind memoryBindToMiddle :: forall (ibargs :: [(*, ImageBufferArg)]) (i :: Nat) sd sm. RawOffsetToOffset ibargs i => D sd -> MemoryBind sm ibargs i -> IO MemoryBind memoryBindToMiddle D sd dv MemoryBind { memoryBindSubresource :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Subresource memoryBindSubresource = Subresource sr, memoryBindOffset :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Offset3d memoryBindOffset = Offset3d ost, memoryBindExtent :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> Extent3d memoryBindExtent = Extent3d ex, memoryBindMemory :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> M sm ibargs memoryBindMemory = m :: M sm ibargs m@(Memory.M IORef (PL (U2 ImageBuffer) ibargs) _ M mm), memoryBindMemoryOffset :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> RawOffset i memoryBindMemoryOffset = RawOffset i most, memoryBindFlags :: forall sm (ibargs :: [(*, ImageBufferArg)]) (i :: Nat). MemoryBind sm ibargs i -> MemoryBindFlags memoryBindFlags = MemoryBindFlags fs } = do mmo <- D sd -> M sm ibargs -> RawOffset i -> IO Size forall (ibargs :: [(*, ImageBufferArg)]) (n :: Nat) sd sm. RawOffsetToOffset ibargs n => D sd -> M sm ibargs -> RawOffset n -> IO Size Memory.rawOffset D sd dv M sm ibargs m RawOffset i most pure M.MemoryBind { M.memoryBindSubresource = sr, M.memoryBindOffset = ost, M.memoryBindExtent = ex, M.memoryBindMemory = mm, M.memoryBindMemoryOffset = mmo, M.memoryBindFlags = fs } class MemoryBindsToMiddle sais where memoryBindsToMiddle :: Device.D sd -> HPList.PL (U3 MemoryBind) sais -> IO [M.MemoryBind] instance MemoryBindsToMiddle '[] where memoryBindsToMiddle :: forall sd. D sd -> PL (U3 MemoryBind) '[] -> IO [MemoryBind] memoryBindsToMiddle D sd _ PL (U3 MemoryBind) '[] HPList.Nil = [MemoryBind] -> IO [MemoryBind] forall a. a -> IO a forall (f :: * -> *) a. Applicative f => a -> f a pure [] instance (Memory.RawOffsetToOffset ibargs i, MemoryBindsToMiddle sais) => MemoryBindsToMiddle ('(sm, ibargs, i) ': sais) where memoryBindsToMiddle :: forall sd. D sd -> PL (U3 MemoryBind) ('(sm, ibargs, i) : sais) -> IO [MemoryBind] memoryBindsToMiddle D sd dv (U3 MemoryBind s1 s2 s3 mb :** PL (U3 MemoryBind) ss1 mbs) = (:) (MemoryBind -> [MemoryBind] -> [MemoryBind]) -> IO MemoryBind -> IO ([MemoryBind] -> [MemoryBind]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> D sd -> MemoryBind s1 s2 s3 -> IO MemoryBind forall (ibargs :: [(*, ImageBufferArg)]) (i :: Nat) sd sm. RawOffsetToOffset ibargs i => D sd -> MemoryBind sm ibargs i -> IO MemoryBind memoryBindToMiddle D sd dv MemoryBind s1 s2 s3 mb IO ([MemoryBind] -> [MemoryBind]) -> IO [MemoryBind] -> IO [MemoryBind] forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> D sd -> PL (U3 MemoryBind) ss1 -> IO [MemoryBind] forall (sais :: [(*, [(*, ImageBufferArg)], Nat)]) sd. MemoryBindsToMiddle sais => D sd -> PL (U3 MemoryBind) sais -> IO [MemoryBind] forall sd. D sd -> PL (U3 MemoryBind) ss1 -> IO [MemoryBind] memoryBindsToMiddle D sd dv PL (U3 MemoryBind) ss1 mbs