module Data.SpirV.Reflect.InterfaceVariable ( InterfaceVariable(..) , WordOffset(..) ) where import Data.Text (Text) import Data.Vector (Vector) import Data.Word (Word32) import GHC.Generics (Generic) import Data.SpirV.Reflect.Enums qualified as Enums import Data.SpirV.Reflect.Traits qualified as Traits import Data.SpirV.Reflect.TypeDescription (TypeDescription) data InterfaceVariable = InterfaceVariable { InterfaceVariable -> Maybe Word32 spirv_id :: Maybe Word32 , InterfaceVariable -> Maybe Text name :: Maybe Text , InterfaceVariable -> Word32 location :: Word32 , InterfaceVariable -> StorageClass storage_class :: Enums.StorageClass , InterfaceVariable -> Maybe Text semantic :: Maybe Text , InterfaceVariable -> DecorationFlags decoration_flags :: Enums.DecorationFlags , InterfaceVariable -> BuiltIn built_in :: Enums.BuiltIn , InterfaceVariable -> Numeric numeric :: Traits.Numeric , InterfaceVariable -> Array array :: Traits.Array , InterfaceVariable -> Vector InterfaceVariable members :: Vector InterfaceVariable , InterfaceVariable -> Format format :: Enums.Format , InterfaceVariable -> Maybe TypeDescription type_description :: Maybe TypeDescription , InterfaceVariable -> WordOffset word_offset :: WordOffset } deriving (InterfaceVariable -> InterfaceVariable -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: InterfaceVariable -> InterfaceVariable -> Bool $c/= :: InterfaceVariable -> InterfaceVariable -> Bool == :: InterfaceVariable -> InterfaceVariable -> Bool $c== :: InterfaceVariable -> InterfaceVariable -> Bool Eq, Int -> InterfaceVariable -> ShowS [InterfaceVariable] -> ShowS InterfaceVariable -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [InterfaceVariable] -> ShowS $cshowList :: [InterfaceVariable] -> ShowS show :: InterfaceVariable -> String $cshow :: InterfaceVariable -> String showsPrec :: Int -> InterfaceVariable -> ShowS $cshowsPrec :: Int -> InterfaceVariable -> ShowS Show, forall x. Rep InterfaceVariable x -> InterfaceVariable forall x. InterfaceVariable -> Rep InterfaceVariable x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep InterfaceVariable x -> InterfaceVariable $cfrom :: forall x. InterfaceVariable -> Rep InterfaceVariable x Generic) newtype WordOffset = WordOffset { WordOffset -> Word32 location :: Word32 } deriving (WordOffset -> WordOffset -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: WordOffset -> WordOffset -> Bool $c/= :: WordOffset -> WordOffset -> Bool == :: WordOffset -> WordOffset -> Bool $c== :: WordOffset -> WordOffset -> Bool Eq, Int -> WordOffset -> ShowS [WordOffset] -> ShowS WordOffset -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [WordOffset] -> ShowS $cshowList :: [WordOffset] -> ShowS show :: WordOffset -> String $cshow :: WordOffset -> String showsPrec :: Int -> WordOffset -> ShowS $cshowsPrec :: Int -> WordOffset -> ShowS Show, forall x. Rep WordOffset x -> WordOffset forall x. WordOffset -> Rep WordOffset x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep WordOffset x -> WordOffset $cfrom :: forall x. WordOffset -> Rep WordOffset x Generic)