Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- invoke :: MonadIO m => FilePath -> m Module
- data Reflect stages = Reflect {
- bindMap :: BindMap BlockBinding
- interfaces :: StageInterface stages
- inputStage :: Text
- inputs :: InterfaceBinds
- type BindMap a = IntMap (IntMap a)
- type StageInterface stages = stages (Maybe (InterfaceBinds, InterfaceBinds))
- type InterfaceBinds = IntMap InterfaceBinding
- type BlockBinding = (Text, DescriptorType, Maybe (Tree ([Maybe Text], BlockSignature)))
- data BlockSignature = BlockSignature {}
- stagesBindMap :: (MonadIO m, MonadReader env m, HasLogFunc env, StageInfo stages) => stages (Maybe Module) -> m (BindMap BlockBinding)
- moduleBindMap :: Module -> BindMap BlockBinding
- blockTree :: [Maybe Text] -> BlockVariable -> Tree ([Maybe Text], BlockSignature)
- bindMapUnionWith :: (a -> a -> Bool) -> BindMap a -> BindMap a -> Either (Int, Int, a, a) (BindMap a)
- type InterfaceBinding = (Maybe Text, [Text], InterfaceSignature)
- data InterfaceSignature = InterfaceSignature {}
- stagesInterfaceMap :: (MonadIO m, Traversable stages) => stages (Maybe Module) -> m (StageInterface stages)
- moduleInterfaceBinds :: Module -> (InterfaceBinds, InterfaceBinds)
- interfaceBinds :: StorageClass -> Vector InterfaceVariable -> InterfaceBinds
- type IncompatibleInterfaces label = (label, label, Int, Maybe (InterfaceSignature, InterfaceSignature))
- type CompatibleInterfaces label = (label, label, IntMap ([Text], Matching (Maybe Text)))
- type Matching a = Either (a, a) a
- interfaceCompatible :: (StageInfo stages, IsString label) => StageInterface stages -> Either (IncompatibleInterfaces label) [CompatibleInterfaces label]
- inputStageInterface :: (StageInfo stages, IsString label) => StageInterface stages -> Maybe (label, InterfaceBinds)
Documentation
Reflect | |
|
type StageInterface stages = stages (Maybe (InterfaceBinds, InterfaceBinds)) Source #
type InterfaceBinds = IntMap InterfaceBinding Source #
@layout(location=N)
Block variables
type BlockBinding = (Text, DescriptorType, Maybe (Tree ([Maybe Text], BlockSignature))) Source #
uniform Foo { ... } foo;
data BlockSignature Source #
Instances
Show BlockSignature Source # | |
Defined in Engine.SpirV.Reflect showsPrec :: Int -> BlockSignature -> ShowS # show :: BlockSignature -> String # showList :: [BlockSignature] -> ShowS # | |
Eq BlockSignature Source # | |
Defined in Engine.SpirV.Reflect (==) :: BlockSignature -> BlockSignature -> Bool # (/=) :: BlockSignature -> BlockSignature -> Bool # | |
Ord BlockSignature Source # | |
Defined in Engine.SpirV.Reflect compare :: BlockSignature -> BlockSignature -> Ordering # (<) :: BlockSignature -> BlockSignature -> Bool # (<=) :: BlockSignature -> BlockSignature -> Bool # (>) :: BlockSignature -> BlockSignature -> Bool # (>=) :: BlockSignature -> BlockSignature -> Bool # max :: BlockSignature -> BlockSignature -> BlockSignature # min :: BlockSignature -> BlockSignature -> BlockSignature # |
stagesBindMap :: (MonadIO m, MonadReader env m, HasLogFunc env, StageInfo stages) => stages (Maybe Module) -> m (BindMap BlockBinding) Source #
moduleBindMap :: Module -> BindMap BlockBinding Source #
bindMapUnionWith :: (a -> a -> Bool) -> BindMap a -> BindMap a -> Either (Int, Int, a, a) (BindMap a) Source #
Interface variables
type InterfaceBinding = (Maybe Text, [Text], InterfaceSignature) Source #
data InterfaceSignature Source #
Instances
Show InterfaceSignature Source # | |
Defined in Engine.SpirV.Reflect showsPrec :: Int -> InterfaceSignature -> ShowS # show :: InterfaceSignature -> String # showList :: [InterfaceSignature] -> ShowS # | |
Eq InterfaceSignature Source # | |
Defined in Engine.SpirV.Reflect (==) :: InterfaceSignature -> InterfaceSignature -> Bool # (/=) :: InterfaceSignature -> InterfaceSignature -> Bool # | |
Ord InterfaceSignature Source # | |
Defined in Engine.SpirV.Reflect compare :: InterfaceSignature -> InterfaceSignature -> Ordering # (<) :: InterfaceSignature -> InterfaceSignature -> Bool # (<=) :: InterfaceSignature -> InterfaceSignature -> Bool # (>) :: InterfaceSignature -> InterfaceSignature -> Bool # (>=) :: InterfaceSignature -> InterfaceSignature -> Bool # max :: InterfaceSignature -> InterfaceSignature -> InterfaceSignature # min :: InterfaceSignature -> InterfaceSignature -> InterfaceSignature # |
stagesInterfaceMap :: (MonadIO m, Traversable stages) => stages (Maybe Module) -> m (StageInterface stages) Source #
moduleInterfaceBinds :: Module -> (InterfaceBinds, InterfaceBinds) Source #
interfaceBinds :: StorageClass -> Vector InterfaceVariable -> InterfaceBinds Source #
type IncompatibleInterfaces label = (label, label, Int, Maybe (InterfaceSignature, InterfaceSignature)) Source #
interfaceCompatible :: (StageInfo stages, IsString label) => StageInterface stages -> Either (IncompatibleInterfaces label) [CompatibleInterfaces label] Source #
inputStageInterface :: (StageInfo stages, IsString label) => StageInterface stages -> Maybe (label, InterfaceBinds) Source #