{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE ScopedTypeVariables, TypeApplications #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures, TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses, AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs -fno-warn-redundant-constraints #-}
module Gpu.Vulkan.DescriptorSet.BindingAndArrayElem.Buffer where
import GHC.TypeLits
import Gpu.Vulkan.Object qualified as VO
import Gpu.Vulkan.DescriptorSetLayout.Type qualified as Lyt
class BindingAndArrayElemBuffer
(lbts :: [Lyt.BindingType]) (objs :: [VO.O]) (i :: Nat) where
bindingAndArrayElemBuffer :: Integral n => n -> n -> (n, n)
instance IsPrefixObject objs lobjs => BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Static al 'Nothing ot t ': lobjs) ': lbts)
(VO.Static al ('Just _nm) ot t ': objs) 0 where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = (n
b, n
ae)
instance IsPrefixObject objs lobjs => BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Static al ('Just _nm) ot t ': lobjs) ': lbts)
(VO.Static al 'Nothing ot t ': objs) 0 where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = (n
b, n
ae)
instance IsPrefixObject objs lobjs => BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Dynamic n al 'Nothing ot t ': lobjs) ': lbts)
(VO.Dynamic n al ('Just _nm) ot t ': objs) 0 where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = (n
b, n
ae)
instance IsPrefixObject objs lobjs => BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Dynamic n al ('Just _nm) ot t ': lobjs) ': lbts)
(VO.Dynamic n al 'Nothing ot t ': objs) 0 where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = (n
b, n
ae)
instance IsPrefixObject objs lobjs => BindingAndArrayElemBuffer
('Lyt.Buffer (obj ': lobjs) ': lbts) (obj ': objs) 0 where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = (n
b, n
ae)
instance {-# OVERLAPPABLE #-}
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts)
(VO.Static al ('Just nm) ot t ': objs) (i - 1) =>
BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Static al 'Nothing ot t ': lobjs) ': lbts)
(VO.Static al ('Just nm) ot t ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(VO.Static al ('Just nm) ot t ': objs) @(i - 1) n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-} (
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts)
(VO.Static al 'Nothing ot t ': objs) (i - 1) ) =>
BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Static al ('Just _nm) ot t ': lobjs) ': lbts)
(VO.Static al 'Nothing ot t ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae = forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(VO.Static al 'Nothing ot t ': objs) @(i - 1) n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-} (
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts)
(VO.Dynamic n al ('Just nm) ot t ': objs) (i - 1) ) =>
BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Dynamic n al 'Nothing ot t ': lobjs) ': lbts)
(VO.Dynamic n al ('Just nm) ot t ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae =
forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(VO.Dynamic n al ('Just nm) ot t ': objs) @(i - 1)
n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-} (
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts)
(VO.Dynamic n al 'Nothing ot t ': objs) (i - 1) ) =>
BindingAndArrayElemBuffer
('Lyt.Buffer (VO.Dynamic n al ('Just _nm) ot t ': lobjs) ': lbts)
(VO.Dynamic n al 'Nothing ot t ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae =
forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(VO.Dynamic n al 'Nothing ot t ': objs) @(i - 1)
n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-} (
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts)
(obj ': objs) (i - 1) ) =>
BindingAndArrayElemBuffer
('Lyt.Buffer (obj ': lobjs) ': lbts) (obj ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae =
forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(obj ': objs) @(i - 1) n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-}
BindingAndArrayElemBuffer ('Lyt.Buffer lobjs ': lbts) (obj ': objs) i =>
BindingAndArrayElemBuffer
('Lyt.Buffer (lobj ': lobjs) ': lbts) (obj ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
ae =
forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer
@('Lyt.Buffer lobjs ': lbts)
@(obj ': objs) @i n
b (n
ae n -> n -> n
forall a. Num a => a -> a -> a
+ n
1)
instance {-# OVERLAPPABLE #-}
BindingAndArrayElemBuffer lbts (obj ': objs) i =>
BindingAndArrayElemBuffer (bt ': lbts) (obj ': objs) i where
bindingAndArrayElemBuffer :: forall n. Integral n => n -> n -> (n, n)
bindingAndArrayElemBuffer n
b n
_ae =
forall (lbts :: [BindingType]) (objs :: [O]) (i :: Alignment) n.
(BindingAndArrayElemBuffer lbts objs i, Integral n) =>
n -> n -> (n, n)
bindingAndArrayElemBuffer @lbts @(obj ': objs) @i (n
b n -> n -> n
forall a. Num a => a -> a -> a
+ n
1) n
0
class IsPrefixObject (objs :: [VO.O]) (objs' :: [VO.O])
instance IsPrefixObject '[] objs'
instance IsPrefixObject objs objs' => IsPrefixObject
(VO.Static al 'Nothing ot t ': objs)
(VO.Static al ('Just _nm) ot t ': objs')
instance IsPrefixObject objs objs' => IsPrefixObject
(VO.Static al ('Just _nm) ot t ': objs)
(VO.Static al 'Nothing ot t ': objs')
instance IsPrefixObject objs objs' => IsPrefixObject
(VO.Dynamic n al 'Nothing ot t ': objs)
(VO.Dynamic n al ('Just _nm) ot t ': objs')
instance IsPrefixObject objs objs' => IsPrefixObject
(VO.Dynamic n al ('Just _nm) ot t ': objs)
(VO.Dynamic n al 'Nothing ot t ': objs')
instance IsPrefixObject objs objs' =>
IsPrefixObject (obj ': objs) (obj ': objs')