module Data.SpirV.Reflect.TypeDescription where
import Data.SpirV.Enum qualified as SpirV
import Data.SpirV.Reflect.Enums qualified as Reflect
import Data.SpirV.Reflect.Traits qualified as Traits
import Data.Text (Text)
import Data.Vector (Vector)
import Data.Word (Word32)
import GHC.Generics (Generic)
data TypeDescription = TypeDescription
{ TypeDescription -> Maybe Word32
id :: Maybe Word32
, TypeDescription -> Maybe Op
op :: Maybe SpirV.Op
, TypeDescription -> Maybe Text
type_name :: Maybe Text
, TypeDescription -> Maybe Text
struct_member_name :: Maybe Text
, TypeDescription -> StorageClass
storage_class :: SpirV.StorageClass
, TypeDescription -> TypeFlags
type_flags :: Reflect.TypeFlags
, TypeDescription -> Maybe Traits
traits :: Maybe Traits
, TypeDescription -> Maybe TypeDescription
struct_type_description :: Maybe TypeDescription
, TypeDescription -> Maybe Word32
copied :: Maybe Word32
, TypeDescription -> Vector TypeDescription
members :: Vector TypeDescription
}
deriving (TypeDescription -> TypeDescription -> Bool
(TypeDescription -> TypeDescription -> Bool)
-> (TypeDescription -> TypeDescription -> Bool)
-> Eq TypeDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeDescription -> TypeDescription -> Bool
== :: TypeDescription -> TypeDescription -> Bool
$c/= :: TypeDescription -> TypeDescription -> Bool
/= :: TypeDescription -> TypeDescription -> Bool
Eq, Int -> TypeDescription -> ShowS
[TypeDescription] -> ShowS
TypeDescription -> String
(Int -> TypeDescription -> ShowS)
-> (TypeDescription -> String)
-> ([TypeDescription] -> ShowS)
-> Show TypeDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeDescription -> ShowS
showsPrec :: Int -> TypeDescription -> ShowS
$cshow :: TypeDescription -> String
show :: TypeDescription -> String
$cshowList :: [TypeDescription] -> ShowS
showList :: [TypeDescription] -> ShowS
Show, (forall x. TypeDescription -> Rep TypeDescription x)
-> (forall x. Rep TypeDescription x -> TypeDescription)
-> Generic TypeDescription
forall x. Rep TypeDescription x -> TypeDescription
forall x. TypeDescription -> Rep TypeDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TypeDescription -> Rep TypeDescription x
from :: forall x. TypeDescription -> Rep TypeDescription x
$cto :: forall x. Rep TypeDescription x -> TypeDescription
to :: forall x. Rep TypeDescription x -> TypeDescription
Generic)
data Traits = Traits
{ Traits -> Numeric
numeric :: Traits.Numeric
, Traits -> Image
image :: Traits.Image
, Traits -> Array
array :: Traits.Array
}
deriving (Traits -> Traits -> Bool
(Traits -> Traits -> Bool)
-> (Traits -> Traits -> Bool) -> Eq Traits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Traits -> Traits -> Bool
== :: Traits -> Traits -> Bool
$c/= :: Traits -> Traits -> Bool
/= :: Traits -> Traits -> Bool
Eq, Int -> Traits -> ShowS
[Traits] -> ShowS
Traits -> String
(Int -> Traits -> ShowS)
-> (Traits -> String) -> ([Traits] -> ShowS) -> Show Traits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Traits -> ShowS
showsPrec :: Int -> Traits -> ShowS
$cshow :: Traits -> String
show :: Traits -> String
$cshowList :: [Traits] -> ShowS
showList :: [Traits] -> ShowS
Show, (forall x. Traits -> Rep Traits x)
-> (forall x. Rep Traits x -> Traits) -> Generic Traits
forall x. Rep Traits x -> Traits
forall x. Traits -> Rep Traits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Traits -> Rep Traits x
from :: forall x. Traits -> Rep Traits x
$cto :: forall x. Rep Traits x -> Traits
to :: forall x. Rep Traits x -> Traits
Generic)
emptyTraits :: Traits
emptyTraits :: Traits
emptyTraits = Traits
{ $sel:numeric:Traits :: Numeric
numeric = Numeric
Traits.emptyNumeric
, $sel:image:Traits :: Image
image = Image
Traits.emptyImage
, $sel:array:Traits :: Array
array = Array
Traits.emptyArray
}