blob: c77e7e365fa668873d1c2536afa07e140b138af2 [file] [log] [blame]
Brian Osman0a442b72020-12-02 11:12:51 -05001/*
2 * Copyright 2020 Google LLC
3 *
4 * Use of this source code is governed by a BSD-style license that can be
5 * found in the LICENSE file.
6 */
7
Ethan Nicholas24c17722021-03-09 13:10:59 -05008#include "include/private/SkSLProgramElement.h"
9#include "include/private/SkSLStatement.h"
Brian Osman0a442b72020-12-02 11:12:51 -050010#include "include/private/SkTArray.h"
Brian Osmanb8ebe232021-01-19 16:33:11 -050011#include "include/private/SkTPin.h"
Brian Osman00185012021-02-04 16:07:11 -050012#include "src/sksl/SkSLCompiler.h"
13#include "src/sksl/SkSLOperators.h"
John Stiles3738ef52021-04-13 10:41:57 -040014#include "src/sksl/codegen/SkSLCodeGenerator.h"
15#include "src/sksl/codegen/SkSLVMCodeGenerator.h"
Brian Osman0a442b72020-12-02 11:12:51 -050016#include "src/sksl/ir/SkSLBinaryExpression.h"
17#include "src/sksl/ir/SkSLBlock.h"
Brian Osman0a442b72020-12-02 11:12:51 -050018#include "src/sksl/ir/SkSLBreakStatement.h"
Brian Osmaneb0f29d2021-08-04 11:34:16 -040019#include "src/sksl/ir/SkSLChildCall.h"
Brian Osman0a442b72020-12-02 11:12:51 -050020#include "src/sksl/ir/SkSLConstructor.h"
John Stiles7384b372021-04-01 13:48:15 -040021#include "src/sksl/ir/SkSLConstructorArray.h"
John Stilese3ae9682021-08-05 10:35:01 -040022#include "src/sksl/ir/SkSLConstructorArrayCast.h"
John Stilese1182782021-03-30 22:09:37 -040023#include "src/sksl/ir/SkSLConstructorDiagonalMatrix.h"
John Stiles5abb9e12021-04-06 13:47:19 -040024#include "src/sksl/ir/SkSLConstructorMatrixResize.h"
John Stiles2938eea2021-04-01 18:58:25 -040025#include "src/sksl/ir/SkSLConstructorSplat.h"
John Stilesd47330f2021-04-08 23:25:52 -040026#include "src/sksl/ir/SkSLConstructorStruct.h"
Brian Osman0a442b72020-12-02 11:12:51 -050027#include "src/sksl/ir/SkSLContinueStatement.h"
28#include "src/sksl/ir/SkSLDoStatement.h"
29#include "src/sksl/ir/SkSLExpressionStatement.h"
30#include "src/sksl/ir/SkSLExternalFunctionCall.h"
Brian Osmanbe0b3b72021-01-06 14:27:35 -050031#include "src/sksl/ir/SkSLExternalFunctionReference.h"
Brian Osman0a442b72020-12-02 11:12:51 -050032#include "src/sksl/ir/SkSLFieldAccess.h"
Brian Osman0a442b72020-12-02 11:12:51 -050033#include "src/sksl/ir/SkSLForStatement.h"
34#include "src/sksl/ir/SkSLFunctionCall.h"
35#include "src/sksl/ir/SkSLFunctionDeclaration.h"
36#include "src/sksl/ir/SkSLFunctionDefinition.h"
37#include "src/sksl/ir/SkSLIfStatement.h"
38#include "src/sksl/ir/SkSLIndexExpression.h"
John Stiles7591d4b2021-09-13 13:32:06 -040039#include "src/sksl/ir/SkSLLiteral.h"
Brian Osman0a442b72020-12-02 11:12:51 -050040#include "src/sksl/ir/SkSLPostfixExpression.h"
41#include "src/sksl/ir/SkSLPrefixExpression.h"
Brian Osman0a442b72020-12-02 11:12:51 -050042#include "src/sksl/ir/SkSLReturnStatement.h"
Brian Osman0a442b72020-12-02 11:12:51 -050043#include "src/sksl/ir/SkSLSwitchStatement.h"
44#include "src/sksl/ir/SkSLSwizzle.h"
45#include "src/sksl/ir/SkSLTernaryExpression.h"
46#include "src/sksl/ir/SkSLVarDeclarations.h"
47#include "src/sksl/ir/SkSLVariableReference.h"
48
49#include <algorithm>
50#include <unordered_map>
51
Mike Kleinff4decc2021-02-10 16:13:35 -060052namespace {
53 // sksl allows the optimizations of fast_mul(), so we want to use that most of the time.
54 // This little sneaky snippet of code lets us use ** as a fast multiply infix operator.
55 struct FastF32 { skvm::F32 val; };
56 static FastF32 operator*(skvm::F32 y) { return {y}; }
57 static skvm::F32 operator*(skvm::F32 x, FastF32 y) { return fast_mul(x, y.val); }
58 static skvm::F32 operator*(float x, FastF32 y) { return fast_mul(x, y.val); }
59}
60
Brian Osman0a442b72020-12-02 11:12:51 -050061namespace SkSL {
62
63namespace {
64
Brian Osman0a442b72020-12-02 11:12:51 -050065// Holds scalars, vectors, or matrices
66struct Value {
67 Value() = default;
68 explicit Value(size_t slots) {
69 fVals.resize(slots);
70 }
71 Value(skvm::F32 x) : fVals({ x.id }) {}
72 Value(skvm::I32 x) : fVals({ x.id }) {}
73
74 explicit operator bool() const { return !fVals.empty(); }
75
76 size_t slots() const { return fVals.size(); }
77
78 struct ValRef {
79 ValRef(skvm::Val& val) : fVal(val) {}
80
81 ValRef& operator=(ValRef v) { fVal = v.fVal; return *this; }
82 ValRef& operator=(skvm::Val v) { fVal = v; return *this; }
83 ValRef& operator=(skvm::F32 v) { fVal = v.id; return *this; }
84 ValRef& operator=(skvm::I32 v) { fVal = v.id; return *this; }
85
86 operator skvm::Val() { return fVal; }
87
88 skvm::Val& fVal;
89 };
90
Brian Osmanf932c692021-01-26 13:54:07 -050091 ValRef operator[](size_t i) {
92 // These redundant asserts work around what we think is a codegen bug in GCC 8.x for
93 // 32-bit x86 Debug builds.
94 SkASSERT(i < fVals.size());
95 return fVals[i];
96 }
97 skvm::Val operator[](size_t i) const {
98 // These redundant asserts work around what we think is a codegen bug in GCC 8.x for
99 // 32-bit x86 Debug builds.
100 SkASSERT(i < fVals.size());
101 return fVals[i];
102 }
Brian Osman0a442b72020-12-02 11:12:51 -0500103
Brian Osmanae87bf12021-05-11 13:36:10 -0400104 SkSpan<skvm::Val> asSpan() { return SkMakeSpan(fVals); }
Brian Osman54515b72021-01-07 14:38:08 -0500105
Brian Osman0a442b72020-12-02 11:12:51 -0500106private:
107 SkSTArray<4, skvm::Val, true> fVals;
108};
109
110} // namespace
111
112class SkVMGenerator {
113public:
114 SkVMGenerator(const Program& program,
Brian Osman0a442b72020-12-02 11:12:51 -0500115 skvm::Builder* builder,
John Stiles137482f2021-07-23 10:38:57 -0400116 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -0400117 SampleColorFilterFn sampleColorFilter,
118 SampleBlenderFn sampleBlender);
Brian Osman0a442b72020-12-02 11:12:51 -0500119
John Stilesa4f56832021-09-22 14:22:33 -0400120 void writeProgram(SkSpan<skvm::Val> uniforms,
121 skvm::Coord device,
122 const FunctionDefinition& function,
123 SkSpan<skvm::Val> arguments,
124 SkSpan<skvm::Val> outReturn);
Brian Osman0a442b72020-12-02 11:12:51 -0500125
126private:
Brian Osman0a442b72020-12-02 11:12:51 -0500127 /**
128 * In SkSL, a Variable represents a named, typed value (along with qualifiers, etc).
Brian Osman21f57072021-01-25 13:51:57 -0500129 * Every Variable is mapped to one (or several, contiguous) indices into our vector of
Brian Osman0a442b72020-12-02 11:12:51 -0500130 * skvm::Val. Those skvm::Val entries hold the current actual value of that variable.
131 *
132 * NOTE: Conceptually, each Variable is just mapped to a Value. We could implement it that way,
Brian Osman21f57072021-01-25 13:51:57 -0500133 * (and eliminate the indirection), but it would add overhead for each Variable,
Brian Osman0a442b72020-12-02 11:12:51 -0500134 * and add additional (different) bookkeeping for things like lvalue-swizzles.
135 *
136 * Any time a variable appears in an expression, that's a VariableReference, which is a kind of
137 * Expression. Evaluating that VariableReference (or any other Expression) produces a Value,
138 * which is a set of skvm::Val. (This allows an Expression to produce a vector or matrix, in
139 * addition to a scalar).
140 *
Brian Osman21f57072021-01-25 13:51:57 -0500141 * For a VariableReference, producing a Value is straightforward - we get the slot of the
142 * Variable (from fVariableMap), use that to look up the current skvm::Vals holding the
143 * variable's contents, and construct a Value with those ids.
Brian Osman0a442b72020-12-02 11:12:51 -0500144 */
145
146 /**
Brian Osman21f57072021-01-25 13:51:57 -0500147 * Returns the slot holding v's Val(s). Allocates storage if this is first time 'v' is
Brian Osman0a442b72020-12-02 11:12:51 -0500148 * referenced. Compound variables (e.g. vectors) will consume more than one slot, with
149 * getSlot returning the start of the contiguous chunk of slots.
150 */
Brian Osman21f57072021-01-25 13:51:57 -0500151 size_t getSlot(const Variable& v);
Brian Osman0a442b72020-12-02 11:12:51 -0500152
John Stilesa4f56832021-09-22 14:22:33 -0400153 /** Initializes uniforms and global variables at the start of main(). */
154 void setupGlobals(SkSpan<skvm::Val> uniforms, skvm::Coord device);
155
156 /** Emits an SkSL function. */
157 void writeFunction(const FunctionDefinition& function,
158 SkSpan<skvm::Val> arguments,
159 SkSpan<skvm::Val> outReturn);
160
Mike Kleinaebcf732021-01-14 10:15:00 -0600161 skvm::F32 f32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
162 skvm::I32 i32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
Brian Osman0a442b72020-12-02 11:12:51 -0500163
164 // Shorthand for scalars
165 skvm::F32 f32(const Value& v) { SkASSERT(v.slots() == 1); return f32(v[0]); }
166 skvm::I32 i32(const Value& v) { SkASSERT(v.slots() == 1); return i32(v[0]); }
167
168 template <typename Fn>
169 Value unary(const Value& v, Fn&& fn) {
170 Value result(v.slots());
171 for (size_t i = 0; i < v.slots(); ++i) {
172 result[i] = fn({fBuilder, v[i]});
173 }
174 return result;
175 }
176
Brian Osman54515b72021-01-07 14:38:08 -0500177 skvm::I32 mask() {
178 // As we encounter (possibly conditional) return statements, fReturned is updated to store
179 // the lanes that have already returned. For the remainder of the current function, those
180 // lanes should be disabled.
Brian Osman9333c872021-01-13 15:06:17 -0500181 return fConditionMask & fLoopMask & ~currentFunction().fReturned;
Brian Osman54515b72021-01-07 14:38:08 -0500182 }
Brian Osman0a442b72020-12-02 11:12:51 -0500183
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500184 size_t fieldSlotOffset(const FieldAccess& expr);
185 size_t indexSlotOffset(const IndexExpression& expr);
186
Brian Osman0a442b72020-12-02 11:12:51 -0500187 Value writeExpression(const Expression& expr);
188 Value writeBinaryExpression(const BinaryExpression& b);
John Stilesd986f472021-04-06 15:54:43 -0400189 Value writeAggregationConstructor(const AnyConstructor& c);
Brian Osmaneb0f29d2021-08-04 11:34:16 -0400190 Value writeChildCall(const ChildCall& c);
John Stilese1182782021-03-30 22:09:37 -0400191 Value writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& c);
John Stiles5abb9e12021-04-06 13:47:19 -0400192 Value writeConstructorMatrixResize(const ConstructorMatrixResize& c);
John Stilesb14a8192021-04-05 11:40:46 -0400193 Value writeConstructorCast(const AnyConstructor& c);
John Stiles2938eea2021-04-01 18:58:25 -0400194 Value writeConstructorSplat(const ConstructorSplat& c);
Brian Osman0a442b72020-12-02 11:12:51 -0500195 Value writeFunctionCall(const FunctionCall& c);
Brian Osmandd50b0c2021-01-11 17:04:29 -0500196 Value writeExternalFunctionCall(const ExternalFunctionCall& c);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500197 Value writeFieldAccess(const FieldAccess& expr);
John Stiles7591d4b2021-09-13 13:32:06 -0400198 Value writeLiteral(const Literal& l);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500199 Value writeIndexExpression(const IndexExpression& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500200 Value writeIntrinsicCall(const FunctionCall& c);
201 Value writePostfixExpression(const PostfixExpression& p);
202 Value writePrefixExpression(const PrefixExpression& p);
203 Value writeSwizzle(const Swizzle& swizzle);
204 Value writeTernaryExpression(const TernaryExpression& t);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500205 Value writeVariableExpression(const VariableReference& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500206
John Stilesfd7252f2021-04-04 22:24:40 -0400207 Value writeTypeConversion(const Value& src, Type::NumberKind srcKind, Type::NumberKind dstKind);
208
Brian Osman0a442b72020-12-02 11:12:51 -0500209 void writeStatement(const Statement& s);
210 void writeBlock(const Block& b);
Brian Osman9333c872021-01-13 15:06:17 -0500211 void writeBreakStatement();
212 void writeContinueStatement();
213 void writeForStatement(const ForStatement& f);
Brian Osman0a442b72020-12-02 11:12:51 -0500214 void writeIfStatement(const IfStatement& stmt);
215 void writeReturnStatement(const ReturnStatement& r);
John Stilescb400082021-09-23 11:07:32 -0400216 void writeSwitchStatement(const SwitchStatement& s);
Brian Osman0a442b72020-12-02 11:12:51 -0500217 void writeVarDeclaration(const VarDeclaration& decl);
218
219 Value writeStore(const Expression& lhs, const Value& rhs);
John Stilescb400082021-09-23 11:07:32 -0400220 void writeStore(SkSpan<size_t> slots, const Value& rhs);
Brian Osman0a442b72020-12-02 11:12:51 -0500221
222 Value writeMatrixInverse2x2(const Value& m);
223 Value writeMatrixInverse3x3(const Value& m);
224 Value writeMatrixInverse4x4(const Value& m);
225
Brian Osmandb2dad52021-01-07 14:08:30 -0500226 //
227 // Global state for the lifetime of the generator:
228 //
Brian Osman0a442b72020-12-02 11:12:51 -0500229 const Program& fProgram;
Brian Osman0a442b72020-12-02 11:12:51 -0500230 skvm::Builder* fBuilder;
231
John Stiles137482f2021-07-23 10:38:57 -0400232 const SampleShaderFn fSampleShader;
233 const SampleColorFilterFn fSampleColorFilter;
John Stiles2955c262021-07-23 15:51:05 -0400234 const SampleBlenderFn fSampleBlender;
Brian Osman0a442b72020-12-02 11:12:51 -0500235
236 // [Variable, first slot in fSlots]
Brian Osman21f57072021-01-25 13:51:57 -0500237 std::unordered_map<const Variable*, size_t> fVariableMap;
Brian Osmandb2dad52021-01-07 14:08:30 -0500238 std::vector<skvm::Val> fSlots;
Brian Osman0a442b72020-12-02 11:12:51 -0500239
Brian Osman9333c872021-01-13 15:06:17 -0500240 // Conditional execution mask (managed by ScopedCondition, and tied to control-flow scopes)
241 skvm::I32 fConditionMask;
242
243 // Similar: loop execution masks. Each loop starts with all lanes active (fLoopMask).
244 // 'break' disables a lane in fLoopMask until the loop finishes
245 // 'continue' disables a lane in fLoopMask, and sets fContinueMask to be re-enabled on the next
246 // iteration
247 skvm::I32 fLoopMask;
248 skvm::I32 fContinueMask;
Brian Osman54515b72021-01-07 14:38:08 -0500249
Brian Osmandb2dad52021-01-07 14:08:30 -0500250 //
251 // State that's local to the generation of a single function:
252 //
Brian Osman54515b72021-01-07 14:38:08 -0500253 struct Function {
254 const SkSpan<skvm::Val> fReturnValue;
255 skvm::I32 fReturned;
256 };
257 std::vector<Function> fFunctionStack;
258 Function& currentFunction() { return fFunctionStack.back(); }
Brian Osman0a442b72020-12-02 11:12:51 -0500259
Brian Osman9333c872021-01-13 15:06:17 -0500260 class ScopedCondition {
Brian Osman0a442b72020-12-02 11:12:51 -0500261 public:
Brian Osman9333c872021-01-13 15:06:17 -0500262 ScopedCondition(SkVMGenerator* generator, skvm::I32 mask)
263 : fGenerator(generator), fOldConditionMask(fGenerator->fConditionMask) {
264 fGenerator->fConditionMask &= mask;
Brian Osman0a442b72020-12-02 11:12:51 -0500265 }
266
Brian Osman9333c872021-01-13 15:06:17 -0500267 ~ScopedCondition() { fGenerator->fConditionMask = fOldConditionMask; }
Brian Osman0a442b72020-12-02 11:12:51 -0500268
269 private:
270 SkVMGenerator* fGenerator;
Brian Osman9333c872021-01-13 15:06:17 -0500271 skvm::I32 fOldConditionMask;
Brian Osman0a442b72020-12-02 11:12:51 -0500272 };
273};
274
275static Type::NumberKind base_number_kind(const Type& type) {
276 if (type.typeKind() == Type::TypeKind::kMatrix || type.typeKind() == Type::TypeKind::kVector) {
277 return base_number_kind(type.componentType());
278 }
279 return type.numberKind();
280}
281
282static inline bool is_uniform(const SkSL::Variable& var) {
283 return var.modifiers().fFlags & Modifiers::kUniform_Flag;
284}
285
Brian Osman0a442b72020-12-02 11:12:51 -0500286SkVMGenerator::SkVMGenerator(const Program& program,
Brian Osman0a442b72020-12-02 11:12:51 -0500287 skvm::Builder* builder,
John Stiles137482f2021-07-23 10:38:57 -0400288 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -0400289 SampleColorFilterFn sampleColorFilter,
290 SampleBlenderFn sampleBlender)
Brian Osman0a442b72020-12-02 11:12:51 -0500291 : fProgram(program)
Brian Osman0a442b72020-12-02 11:12:51 -0500292 , fBuilder(builder)
John Stiles137482f2021-07-23 10:38:57 -0400293 , fSampleShader(std::move(sampleShader))
John Stiles2955c262021-07-23 15:51:05 -0400294 , fSampleColorFilter(std::move(sampleColorFilter))
John Stilesa4f56832021-09-22 14:22:33 -0400295 , fSampleBlender(std::move(sampleBlender)) {}
296
297void SkVMGenerator::writeProgram(SkSpan<skvm::Val> uniforms,
298 skvm::Coord device,
299 const FunctionDefinition& function,
300 SkSpan<skvm::Val> arguments,
301 SkSpan<skvm::Val> outReturn) {
Brian Osman9333c872021-01-13 15:06:17 -0500302 fConditionMask = fLoopMask = fBuilder->splat(0xffff'ffff);
Brian Osman0a442b72020-12-02 11:12:51 -0500303
John Stilesa4f56832021-09-22 14:22:33 -0400304 this->setupGlobals(uniforms, device);
305 this->writeFunction(function, arguments, outReturn);
306}
307
308void SkVMGenerator::setupGlobals(SkSpan<skvm::Val> uniforms, skvm::Coord device) {
309 // Add storage for each global variable (including uniforms) to fSlots, and entries in
Brian Osman0a442b72020-12-02 11:12:51 -0500310 // fVariableMap to remember where every variable is stored.
311 const skvm::Val* uniformIter = uniforms.begin();
312 size_t fpCount = 0;
313 for (const ProgramElement* e : fProgram.elements()) {
314 if (e->is<GlobalVarDeclaration>()) {
Brian Osmanc0576692021-02-17 13:52:35 -0500315 const GlobalVarDeclaration& gvd = e->as<GlobalVarDeclaration>();
316 const VarDeclaration& decl = gvd.declaration()->as<VarDeclaration>();
317 const Variable& var = decl.var();
Brian Osman0a442b72020-12-02 11:12:51 -0500318 SkASSERT(fVariableMap.find(&var) == fVariableMap.end());
319
Brian Osman14d00962021-04-02 17:04:35 -0400320 // For most variables, fVariableMap stores an index into fSlots, but for children,
John Stiles2955c262021-07-23 15:51:05 -0400321 // fVariableMap stores the index to pass to fSample(Shader|ColorFilter|Blender)
Brian Osman14d00962021-04-02 17:04:35 -0400322 if (var.type().isEffectChild()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500323 fVariableMap[&var] = fpCount++;
324 continue;
325 }
326
327 // Opaque types include fragment processors, GL objects (samplers, textures, etc), and
328 // special types like 'void'. Of those, only fragment processors are legal variables.
329 SkASSERT(!var.type().isOpaque());
330
Brian Osmanc0576692021-02-17 13:52:35 -0500331 // getSlot() allocates space for the variable's value in fSlots, initializes it to zero,
332 // and populates fVariableMap.
333 size_t slot = this->getSlot(var),
John Stiles47b087e2021-04-06 13:19:35 -0400334 nslots = var.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500335
John Stilesa4f56832021-09-22 14:22:33 -0400336 // builtin variables are system-defined, with special semantics. The only builtin
337 // variable exposed to runtime effects is sk_FragCoord.
Brian Osman0a442b72020-12-02 11:12:51 -0500338 if (int builtin = var.modifiers().fLayout.fBuiltin; builtin >= 0) {
Brian Osman0a442b72020-12-02 11:12:51 -0500339 switch (builtin) {
340 case SK_FRAGCOORD_BUILTIN:
341 SkASSERT(nslots == 4);
Brian Osmanc0576692021-02-17 13:52:35 -0500342 fSlots[slot + 0] = device.x.id;
343 fSlots[slot + 1] = device.y.id;
344 fSlots[slot + 2] = fBuilder->splat(0.0f).id;
345 fSlots[slot + 3] = fBuilder->splat(1.0f).id;
Brian Osman0a442b72020-12-02 11:12:51 -0500346 break;
347 default:
John Stilescb400082021-09-23 11:07:32 -0400348 SkDEBUGFAILF("Unsupported builtin %d", builtin);
Brian Osman0a442b72020-12-02 11:12:51 -0500349 }
John Stilesa4f56832021-09-22 14:22:33 -0400350 continue;
351 }
352
353 // For uniforms, copy the supplied IDs over
354 if (is_uniform(var)) {
Brian Osman0a442b72020-12-02 11:12:51 -0500355 SkASSERT(uniformIter + nslots <= uniforms.end());
Brian Osmanc0576692021-02-17 13:52:35 -0500356 std::copy(uniformIter, uniformIter + nslots, fSlots.begin() + slot);
Brian Osman0a442b72020-12-02 11:12:51 -0500357 uniformIter += nslots;
John Stilesa4f56832021-09-22 14:22:33 -0400358 continue;
359 }
360
361 // For other globals, populate with the initializer expression (if there is one)
362 if (decl.value()) {
Brian Osmanc0576692021-02-17 13:52:35 -0500363 Value val = this->writeExpression(*decl.value());
364 for (size_t i = 0; i < nslots; ++i) {
365 fSlots[slot + i] = val[i];
366 }
Brian Osman0a442b72020-12-02 11:12:51 -0500367 }
368 }
369 }
370 SkASSERT(uniformIter == uniforms.end());
Brian Osman0a442b72020-12-02 11:12:51 -0500371}
372
Brian Osmandb2dad52021-01-07 14:08:30 -0500373void SkVMGenerator::writeFunction(const FunctionDefinition& function,
374 SkSpan<skvm::Val> arguments,
375 SkSpan<skvm::Val> outReturn) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500376 const FunctionDeclaration& decl = function.declaration();
John Stiles47b087e2021-04-06 13:19:35 -0400377 SkASSERT(decl.returnType().slotCount() == outReturn.size());
Brian Osmandb2dad52021-01-07 14:08:30 -0500378
Brian Osman54515b72021-01-07 14:38:08 -0500379 fFunctionStack.push_back({outReturn, /*returned=*/fBuilder->splat(0)});
Brian Osmandb2dad52021-01-07 14:08:30 -0500380
381 // For all parameters, copy incoming argument IDs to our vector of (all) variable IDs
Brian Osman5933d4c2021-01-05 13:02:20 -0500382 size_t argIdx = 0;
Brian Osmandb2dad52021-01-07 14:08:30 -0500383 for (const Variable* p : decl.parameters()) {
Brian Osman21f57072021-01-25 13:51:57 -0500384 size_t paramSlot = this->getSlot(*p),
John Stiles47b087e2021-04-06 13:19:35 -0400385 nslots = p->type().slotCount();
Brian Osman5933d4c2021-01-05 13:02:20 -0500386
Brian Osmandb2dad52021-01-07 14:08:30 -0500387 for (size_t i = 0; i < nslots; ++i) {
388 fSlots[paramSlot + i] = arguments[argIdx + i];
389 }
390 argIdx += nslots;
391 }
392 SkASSERT(argIdx == arguments.size());
393
394 this->writeStatement(*function.body());
395
396 // Copy 'out' and 'inout' parameters back to their caller-supplied argument storage
397 argIdx = 0;
398 for (const Variable* p : decl.parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -0400399 size_t nslots = p->type().slotCount();
Brian Osmandb2dad52021-01-07 14:08:30 -0500400
Brian Osman5933d4c2021-01-05 13:02:20 -0500401 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
Brian Osman21f57072021-01-25 13:51:57 -0500402 size_t paramSlot = this->getSlot(*p);
Brian Osman5933d4c2021-01-05 13:02:20 -0500403 for (size_t i = 0; i < nslots; ++i) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500404 arguments[argIdx + i] = fSlots[paramSlot + i];
Brian Osman5933d4c2021-01-05 13:02:20 -0500405 }
406 }
407 argIdx += nslots;
408 }
Brian Osmandb2dad52021-01-07 14:08:30 -0500409 SkASSERT(argIdx == arguments.size());
Brian Osman54515b72021-01-07 14:38:08 -0500410
411 fFunctionStack.pop_back();
Brian Osman0a442b72020-12-02 11:12:51 -0500412}
413
Brian Osman21f57072021-01-25 13:51:57 -0500414size_t SkVMGenerator::getSlot(const Variable& v) {
Brian Osman0a442b72020-12-02 11:12:51 -0500415 auto entry = fVariableMap.find(&v);
416 if (entry != fVariableMap.end()) {
417 return entry->second;
418 }
419
Brian Osman0a442b72020-12-02 11:12:51 -0500420 size_t slot = fSlots.size(),
John Stiles47b087e2021-04-06 13:19:35 -0400421 nslots = v.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500422 fSlots.resize(slot + nslots, fBuilder->splat(0.0f).id);
423 fVariableMap[&v] = slot;
424 return slot;
425}
426
Brian Osman0a442b72020-12-02 11:12:51 -0500427Value SkVMGenerator::writeBinaryExpression(const BinaryExpression& b) {
428 const Expression& left = *b.left();
429 const Expression& right = *b.right();
John Stiles45990502021-02-16 10:55:27 -0500430 Operator op = b.getOperator();
431 if (op.kind() == Token::Kind::TK_EQ) {
Brian Osman0a442b72020-12-02 11:12:51 -0500432 return this->writeStore(left, this->writeExpression(right));
433 }
434
435 const Type& lType = left.type();
436 const Type& rType = right.type();
437 bool lVecOrMtx = (lType.isVector() || lType.isMatrix());
438 bool rVecOrMtx = (rType.isVector() || rType.isMatrix());
John Stiles45990502021-02-16 10:55:27 -0500439 bool isAssignment = op.isAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500440 if (isAssignment) {
John Stiles45990502021-02-16 10:55:27 -0500441 op = op.removeAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500442 }
443 Type::NumberKind nk = base_number_kind(lType);
444
445 // A few ops require special treatment:
John Stiles45990502021-02-16 10:55:27 -0500446 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500447 case Token::Kind::TK_LOGICALAND: {
448 SkASSERT(!isAssignment);
449 SkASSERT(nk == Type::NumberKind::kBoolean);
450 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500451 ScopedCondition shortCircuit(this, lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500452 skvm::I32 rVal = i32(this->writeExpression(right));
453 return lVal & rVal;
454 }
455 case Token::Kind::TK_LOGICALOR: {
456 SkASSERT(!isAssignment);
457 SkASSERT(nk == Type::NumberKind::kBoolean);
458 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500459 ScopedCondition shortCircuit(this, ~lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500460 skvm::I32 rVal = i32(this->writeExpression(right));
461 return lVal | rVal;
462 }
John Stiles94e72b92021-01-30 11:06:18 -0500463 case Token::Kind::TK_COMMA:
464 // We write the left side of the expression to preserve its side effects, even though we
465 // immediately discard the result.
466 this->writeExpression(left);
467 return this->writeExpression(right);
Brian Osman0a442b72020-12-02 11:12:51 -0500468 default:
469 break;
470 }
471
472 // All of the other ops always evaluate both sides of the expression
473 Value lVal = this->writeExpression(left),
474 rVal = this->writeExpression(right);
475
476 // Special case for M*V, V*M, M*M (but not V*V!)
John Stiles45990502021-02-16 10:55:27 -0500477 if (op.kind() == Token::Kind::TK_STAR
Brian Osman0a442b72020-12-02 11:12:51 -0500478 && lVecOrMtx && rVecOrMtx && !(lType.isVector() && rType.isVector())) {
479 int rCols = rType.columns(),
480 rRows = rType.rows(),
481 lCols = lType.columns(),
482 lRows = lType.rows();
483 // M*V treats the vector as a column
484 if (rType.isVector()) {
485 std::swap(rCols, rRows);
486 }
487 SkASSERT(lCols == rRows);
John Stiles47b087e2021-04-06 13:19:35 -0400488 SkASSERT(b.type().slotCount() == static_cast<size_t>(lRows * rCols));
Brian Osman0a442b72020-12-02 11:12:51 -0500489 Value result(lRows * rCols);
490 size_t resultIdx = 0;
John Stiles727adfe2021-09-14 14:07:23 -0400491 const skvm::F32 zero = fBuilder->splat(0.0f);
Brian Osman0a442b72020-12-02 11:12:51 -0500492 for (int c = 0; c < rCols; ++c)
493 for (int r = 0; r < lRows; ++r) {
John Stiles727adfe2021-09-14 14:07:23 -0400494 skvm::F32 sum = zero;
Brian Osman0a442b72020-12-02 11:12:51 -0500495 for (int j = 0; j < lCols; ++j) {
496 sum += f32(lVal[j*lRows + r]) * f32(rVal[c*rRows + j]);
497 }
498 result[resultIdx++] = sum;
499 }
500 SkASSERT(resultIdx == result.slots());
501 return isAssignment ? this->writeStore(left, result) : result;
502 }
503
504 size_t nslots = std::max(lVal.slots(), rVal.slots());
505
Brian Osman0a442b72020-12-02 11:12:51 -0500506 auto binary = [&](auto&& f_fn, auto&& i_fn) {
507 Value result(nslots);
508 for (size_t i = 0; i < nslots; ++i) {
509 // If one side is scalar, replicate it to all channels
510 skvm::Val L = lVal.slots() == 1 ? lVal[0] : lVal[i],
511 R = rVal.slots() == 1 ? rVal[0] : rVal[i];
512 if (nk == Type::NumberKind::kFloat) {
513 result[i] = f_fn(f32(L), f32(R));
514 } else {
515 result[i] = i_fn(i32(L), i32(R));
516 }
517 }
518 return isAssignment ? this->writeStore(left, result) : result;
519 };
520
521 auto unsupported_f = [&](skvm::F32, skvm::F32) {
522 SkDEBUGFAIL("Unsupported operator");
523 return skvm::F32{};
524 };
525
John Stiles45990502021-02-16 10:55:27 -0500526 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500527 case Token::Kind::TK_EQEQ: {
528 SkASSERT(!isAssignment);
529 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x == y; },
530 [](skvm::I32 x, skvm::I32 y) { return x == y; });
531 skvm::I32 folded = i32(cmp[0]);
532 for (size_t i = 1; i < nslots; ++i) {
533 folded &= i32(cmp[i]);
534 }
535 return folded;
536 }
537 case Token::Kind::TK_NEQ: {
538 SkASSERT(!isAssignment);
539 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x != y; },
540 [](skvm::I32 x, skvm::I32 y) { return x != y; });
541 skvm::I32 folded = i32(cmp[0]);
542 for (size_t i = 1; i < nslots; ++i) {
543 folded |= i32(cmp[i]);
544 }
545 return folded;
546 }
547 case Token::Kind::TK_GT:
548 return binary([](skvm::F32 x, skvm::F32 y) { return x > y; },
549 [](skvm::I32 x, skvm::I32 y) { return x > y; });
550 case Token::Kind::TK_GTEQ:
551 return binary([](skvm::F32 x, skvm::F32 y) { return x >= y; },
552 [](skvm::I32 x, skvm::I32 y) { return x >= y; });
553 case Token::Kind::TK_LT:
554 return binary([](skvm::F32 x, skvm::F32 y) { return x < y; },
555 [](skvm::I32 x, skvm::I32 y) { return x < y; });
556 case Token::Kind::TK_LTEQ:
557 return binary([](skvm::F32 x, skvm::F32 y) { return x <= y; },
558 [](skvm::I32 x, skvm::I32 y) { return x <= y; });
559
560 case Token::Kind::TK_PLUS:
561 return binary([](skvm::F32 x, skvm::F32 y) { return x + y; },
562 [](skvm::I32 x, skvm::I32 y) { return x + y; });
563 case Token::Kind::TK_MINUS:
564 return binary([](skvm::F32 x, skvm::F32 y) { return x - y; },
565 [](skvm::I32 x, skvm::I32 y) { return x - y; });
566 case Token::Kind::TK_STAR:
Mike Kleinff4decc2021-02-10 16:13:35 -0600567 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; },
Brian Osman0a442b72020-12-02 11:12:51 -0500568 [](skvm::I32 x, skvm::I32 y) { return x * y; });
569 case Token::Kind::TK_SLASH:
570 // Minimum spec (GLSL ES 1.0) has very loose requirements for integer operations.
571 // (Low-end GPUs may not have integer ALUs). Given that, we are allowed to do floating
572 // point division plus rounding. Section 10.28 of the spec even clarifies that the
573 // rounding mode is undefined (but round-towards-zero is the obvious/common choice).
574 return binary([](skvm::F32 x, skvm::F32 y) { return x / y; },
575 [](skvm::I32 x, skvm::I32 y) {
576 return skvm::trunc(skvm::to_F32(x) / skvm::to_F32(y));
577 });
578
579 case Token::Kind::TK_BITWISEXOR:
580 case Token::Kind::TK_LOGICALXOR:
581 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x ^ y; });
582 case Token::Kind::TK_BITWISEAND:
583 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x & y; });
584 case Token::Kind::TK_BITWISEOR:
585 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x | y; });
586
587 // These three operators are all 'reserved' (illegal) in our minimum spec, but will require
588 // implementation in the future.
589 case Token::Kind::TK_PERCENT:
590 case Token::Kind::TK_SHL:
591 case Token::Kind::TK_SHR:
592 default:
593 SkDEBUGFAIL("Unsupported operator");
594 return {};
595 }
596}
597
John Stilesd986f472021-04-06 15:54:43 -0400598Value SkVMGenerator::writeAggregationConstructor(const AnyConstructor& c) {
John Stiles47b087e2021-04-06 13:19:35 -0400599 Value result(c.type().slotCount());
John Stiles626b62e2021-03-31 22:06:07 -0400600 size_t resultIdx = 0;
John Stilesd986f472021-04-06 15:54:43 -0400601 for (const auto &arg : c.argumentSpan()) {
John Stiles626b62e2021-03-31 22:06:07 -0400602 Value tmp = this->writeExpression(*arg);
603 for (size_t tmpSlot = 0; tmpSlot < tmp.slots(); ++tmpSlot) {
604 result[resultIdx++] = tmp[tmpSlot];
605 }
606 }
607 return result;
608}
609
John Stilesfd7252f2021-04-04 22:24:40 -0400610Value SkVMGenerator::writeTypeConversion(const Value& src,
611 Type::NumberKind srcKind,
612 Type::NumberKind dstKind) {
613 // Conversion among "similar" types (floatN <-> halfN), (shortN <-> intN), etc. is a no-op.
614 if (srcKind == dstKind) {
615 return src;
616 }
617
618 // TODO: Handle signed vs. unsigned. GLSL ES 1.0 only has 'int', so no problem yet.
619 Value dst(src.slots());
620 switch (dstKind) {
621 case Type::NumberKind::kFloat:
622 if (srcKind == Type::NumberKind::kSigned) {
623 // int -> float
624 for (size_t i = 0; i < src.slots(); ++i) {
625 dst[i] = skvm::to_F32(i32(src[i]));
626 }
627 return dst;
628 }
629 if (srcKind == Type::NumberKind::kBoolean) {
630 // bool -> float
631 for (size_t i = 0; i < src.slots(); ++i) {
632 dst[i] = skvm::select(i32(src[i]), 1.0f, 0.0f);
633 }
634 return dst;
635 }
636 break;
637
638 case Type::NumberKind::kSigned:
639 if (srcKind == Type::NumberKind::kFloat) {
640 // float -> int
641 for (size_t i = 0; i < src.slots(); ++i) {
642 dst[i] = skvm::trunc(f32(src[i]));
643 }
644 return dst;
645 }
646 if (srcKind == Type::NumberKind::kBoolean) {
647 // bool -> int
648 for (size_t i = 0; i < src.slots(); ++i) {
649 dst[i] = skvm::select(i32(src[i]), 1, 0);
650 }
651 return dst;
652 }
653 break;
654
655 case Type::NumberKind::kBoolean:
656 if (srcKind == Type::NumberKind::kSigned) {
657 // int -> bool
658 for (size_t i = 0; i < src.slots(); ++i) {
659 dst[i] = i32(src[i]) != 0;
660 }
661 return dst;
662 }
663 if (srcKind == Type::NumberKind::kFloat) {
664 // float -> bool
665 for (size_t i = 0; i < src.slots(); ++i) {
666 dst[i] = f32(src[i]) != 0.0;
667 }
668 return dst;
669 }
670 break;
671
672 default:
673 break;
674 }
John Stiles7bf79992021-06-25 11:05:20 -0400675 SkDEBUGFAILF("Unsupported type conversion: %d -> %d", (int)srcKind, (int)dstKind);
John Stilesfd7252f2021-04-04 22:24:40 -0400676 return {};
677}
678
John Stilesb14a8192021-04-05 11:40:46 -0400679Value SkVMGenerator::writeConstructorCast(const AnyConstructor& c) {
680 auto arguments = c.argumentSpan();
681 SkASSERT(arguments.size() == 1);
682 const Expression& argument = *arguments.front();
683
684 const Type& srcType = argument.type();
John Stilesfd7252f2021-04-04 22:24:40 -0400685 const Type& dstType = c.type();
686 Type::NumberKind srcKind = base_number_kind(srcType);
687 Type::NumberKind dstKind = base_number_kind(dstType);
John Stilesb14a8192021-04-05 11:40:46 -0400688 Value src = this->writeExpression(argument);
John Stilesfd7252f2021-04-04 22:24:40 -0400689 return this->writeTypeConversion(src, srcKind, dstKind);
690}
691
John Stiles2938eea2021-04-01 18:58:25 -0400692Value SkVMGenerator::writeConstructorSplat(const ConstructorSplat& c) {
693 SkASSERT(c.type().isVector());
694 SkASSERT(c.argument()->type().isScalar());
695 int columns = c.type().columns();
696
697 // Splat the argument across all components of a vector.
698 Value src = this->writeExpression(*c.argument());
699 Value dst(columns);
700 for (int i = 0; i < columns; ++i) {
701 dst[i] = src[0];
702 }
703 return dst;
704}
705
John Stiles68f56062021-08-03 12:31:56 -0400706Value SkVMGenerator::writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& ctor) {
707 const Type& dstType = ctor.type();
John Stilese1182782021-03-30 22:09:37 -0400708 SkASSERT(dstType.isMatrix());
John Stiles68f56062021-08-03 12:31:56 -0400709 SkASSERT(ctor.argument()->type() == dstType.componentType());
John Stilese1182782021-03-30 22:09:37 -0400710
John Stiles68f56062021-08-03 12:31:56 -0400711 Value src = this->writeExpression(*ctor.argument());
John Stilese1182782021-03-30 22:09:37 -0400712 Value dst(dstType.rows() * dstType.columns());
713 size_t dstIndex = 0;
714
715 // Matrix-from-scalar builds a diagonal scale matrix
John Stiles727adfe2021-09-14 14:07:23 -0400716 const skvm::F32 zero = fBuilder->splat(0.0f);
John Stilese1182782021-03-30 22:09:37 -0400717 for (int c = 0; c < dstType.columns(); ++c) {
718 for (int r = 0; r < dstType.rows(); ++r) {
John Stiles727adfe2021-09-14 14:07:23 -0400719 dst[dstIndex++] = (c == r ? f32(src) : zero);
John Stilese1182782021-03-30 22:09:37 -0400720 }
721 }
722
723 SkASSERT(dstIndex == dst.slots());
724 return dst;
725}
726
John Stiles68f56062021-08-03 12:31:56 -0400727Value SkVMGenerator::writeConstructorMatrixResize(const ConstructorMatrixResize& ctor) {
728 const Type& srcType = ctor.argument()->type();
729 const Type& dstType = ctor.type();
730 Value src = this->writeExpression(*ctor.argument());
John Stiles5abb9e12021-04-06 13:47:19 -0400731 Value dst(dstType.rows() * dstType.columns());
732
733 // Matrix-from-matrix uses src where it overlaps, and fills in missing fields with identity.
734 size_t dstIndex = 0;
735 for (int c = 0; c < dstType.columns(); ++c) {
736 for (int r = 0; r < dstType.rows(); ++r) {
737 if (c < srcType.columns() && r < srcType.rows()) {
738 dst[dstIndex++] = src[c * srcType.rows() + r];
739 } else {
740 dst[dstIndex++] = fBuilder->splat(c == r ? 1.0f : 0.0f);
741 }
742 }
743 }
744
745 SkASSERT(dstIndex == dst.slots());
746 return dst;
747}
748
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500749size_t SkVMGenerator::fieldSlotOffset(const FieldAccess& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500750 size_t offset = 0;
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500751 for (int i = 0; i < expr.fieldIndex(); ++i) {
John Stiles47b087e2021-04-06 13:19:35 -0400752 offset += (*expr.base()->type().fields()[i].fType).slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500753 }
754 return offset;
755}
756
757Value SkVMGenerator::writeFieldAccess(const FieldAccess& expr) {
758 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400759 Value field(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500760 size_t offset = this->fieldSlotOffset(expr);
761 for (size_t i = 0; i < field.slots(); ++i) {
762 field[i] = base[offset + i];
763 }
764 return field;
765}
766
767size_t SkVMGenerator::indexSlotOffset(const IndexExpression& expr) {
768 Value index = this->writeExpression(*expr.index());
769 int indexValue = -1;
770 SkAssertResult(fBuilder->allImm(index[0], &indexValue));
771
772 // When indexing by a literal, the front-end guarantees that we don't go out of bounds.
773 // But when indexing by a loop variable, it's possible to generate out-of-bounds access.
774 // The GLSL spec leaves that behavior undefined - we'll just clamp everything here.
775 indexValue = SkTPin(indexValue, 0, expr.base()->type().columns() - 1);
776
John Stiles47b087e2021-04-06 13:19:35 -0400777 size_t stride = expr.type().slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500778 return indexValue * stride;
779}
780
781Value SkVMGenerator::writeIndexExpression(const IndexExpression& expr) {
782 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400783 Value element(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500784 size_t offset = this->indexSlotOffset(expr);
785 for (size_t i = 0; i < element.slots(); ++i) {
786 element[i] = base[offset + i];
787 }
788 return element;
789}
790
791Value SkVMGenerator::writeVariableExpression(const VariableReference& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500792 size_t slot = this->getSlot(*expr.variable());
John Stiles47b087e2021-04-06 13:19:35 -0400793 Value val(expr.type().slotCount());
Brian Osman0a442b72020-12-02 11:12:51 -0500794 for (size_t i = 0; i < val.slots(); ++i) {
795 val[i] = fSlots[slot + i];
796 }
797 return val;
798}
799
800Value SkVMGenerator::writeMatrixInverse2x2(const Value& m) {
801 SkASSERT(m.slots() == 4);
802 skvm::F32 a = f32(m[0]),
803 b = f32(m[1]),
804 c = f32(m[2]),
805 d = f32(m[3]);
806 skvm::F32 idet = 1.0f / (a*d - b*c);
807
808 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600809 result[0] = ( d ** idet);
810 result[1] = (-b ** idet);
811 result[2] = (-c ** idet);
812 result[3] = ( a ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500813 return result;
814}
815
816Value SkVMGenerator::writeMatrixInverse3x3(const Value& m) {
817 SkASSERT(m.slots() == 9);
818 skvm::F32 a11 = f32(m[0]), a12 = f32(m[3]), a13 = f32(m[6]),
819 a21 = f32(m[1]), a22 = f32(m[4]), a23 = f32(m[7]),
820 a31 = f32(m[2]), a32 = f32(m[5]), a33 = f32(m[8]);
821 skvm::F32 idet = 1.0f / (a11*a22*a33 + a12*a23*a31 + a13*a21*a32 -
822 a11*a23*a32 - a12*a21*a33 - a13*a22*a31);
823
824 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600825 result[0] = ((a22**a33 - a23**a32) ** idet);
826 result[1] = ((a23**a31 - a21**a33) ** idet);
827 result[2] = ((a21**a32 - a22**a31) ** idet);
828 result[3] = ((a13**a32 - a12**a33) ** idet);
829 result[4] = ((a11**a33 - a13**a31) ** idet);
830 result[5] = ((a12**a31 - a11**a32) ** idet);
831 result[6] = ((a12**a23 - a13**a22) ** idet);
832 result[7] = ((a13**a21 - a11**a23) ** idet);
833 result[8] = ((a11**a22 - a12**a21) ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500834 return result;
835}
836
837Value SkVMGenerator::writeMatrixInverse4x4(const Value& m) {
838 SkASSERT(m.slots() == 16);
839 skvm::F32 a00 = f32(m[0]), a10 = f32(m[4]), a20 = f32(m[ 8]), a30 = f32(m[12]),
840 a01 = f32(m[1]), a11 = f32(m[5]), a21 = f32(m[ 9]), a31 = f32(m[13]),
841 a02 = f32(m[2]), a12 = f32(m[6]), a22 = f32(m[10]), a32 = f32(m[14]),
842 a03 = f32(m[3]), a13 = f32(m[7]), a23 = f32(m[11]), a33 = f32(m[15]);
843
Mike Kleinff4decc2021-02-10 16:13:35 -0600844 skvm::F32 b00 = a00**a11 - a01**a10,
845 b01 = a00**a12 - a02**a10,
846 b02 = a00**a13 - a03**a10,
847 b03 = a01**a12 - a02**a11,
848 b04 = a01**a13 - a03**a11,
849 b05 = a02**a13 - a03**a12,
850 b06 = a20**a31 - a21**a30,
851 b07 = a20**a32 - a22**a30,
852 b08 = a20**a33 - a23**a30,
853 b09 = a21**a32 - a22**a31,
854 b10 = a21**a33 - a23**a31,
855 b11 = a22**a33 - a23**a32;
Brian Osman0a442b72020-12-02 11:12:51 -0500856
Mike Kleinff4decc2021-02-10 16:13:35 -0600857 skvm::F32 idet = 1.0f / (b00**b11 - b01**b10 + b02**b09 + b03**b08 - b04**b07 + b05**b06);
Brian Osman0a442b72020-12-02 11:12:51 -0500858
859 b00 *= idet;
860 b01 *= idet;
861 b02 *= idet;
862 b03 *= idet;
863 b04 *= idet;
864 b05 *= idet;
865 b06 *= idet;
866 b07 *= idet;
867 b08 *= idet;
868 b09 *= idet;
869 b10 *= idet;
870 b11 *= idet;
871
872 Value result(m.slots());
873 result[ 0] = (a11*b11 - a12*b10 + a13*b09);
874 result[ 1] = (a02*b10 - a01*b11 - a03*b09);
875 result[ 2] = (a31*b05 - a32*b04 + a33*b03);
876 result[ 3] = (a22*b04 - a21*b05 - a23*b03);
877 result[ 4] = (a12*b08 - a10*b11 - a13*b07);
878 result[ 5] = (a00*b11 - a02*b08 + a03*b07);
879 result[ 6] = (a32*b02 - a30*b05 - a33*b01);
880 result[ 7] = (a20*b05 - a22*b02 + a23*b01);
881 result[ 8] = (a10*b10 - a11*b08 + a13*b06);
882 result[ 9] = (a01*b08 - a00*b10 - a03*b06);
883 result[10] = (a30*b04 - a31*b02 + a33*b00);
884 result[11] = (a21*b02 - a20*b04 - a23*b00);
885 result[12] = (a11*b07 - a10*b09 - a12*b06);
886 result[13] = (a00*b09 - a01*b07 + a02*b06);
887 result[14] = (a31*b01 - a30*b03 - a32*b00);
888 result[15] = (a20*b03 - a21*b01 + a22*b00);
889 return result;
890}
891
Brian Osmaneb0f29d2021-08-04 11:34:16 -0400892Value SkVMGenerator::writeChildCall(const ChildCall& c) {
893 auto child_it = fVariableMap.find(&c.child());
894 SkASSERT(child_it != fVariableMap.end());
895
896 const Expression* arg = c.arguments()[0].get();
897 Value argVal = this->writeExpression(*arg);
898 skvm::Color color;
899
900 switch (c.child().type().typeKind()) {
901 case Type::TypeKind::kShader: {
902 SkASSERT(c.arguments().size() == 1);
903 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fFloat2);
904 skvm::Coord coord = {f32(argVal[0]), f32(argVal[1])};
905 color = fSampleShader(child_it->second, coord);
906 break;
907 }
908 case Type::TypeKind::kColorFilter: {
909 SkASSERT(c.arguments().size() == 1);
910 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
911 arg->type() == *fProgram.fContext->fTypes.fFloat4);
912 skvm::Color inColor = {f32(argVal[0]), f32(argVal[1]), f32(argVal[2]), f32(argVal[3])};
913 color = fSampleColorFilter(child_it->second, inColor);
914 break;
915 }
916 case Type::TypeKind::kBlender: {
917 SkASSERT(c.arguments().size() == 2);
918 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
919 arg->type() == *fProgram.fContext->fTypes.fFloat4);
920 skvm::Color srcColor = {f32(argVal[0]), f32(argVal[1]), f32(argVal[2]), f32(argVal[3])};
921
922 arg = c.arguments()[1].get();
923 argVal = this->writeExpression(*arg);
924 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
925 arg->type() == *fProgram.fContext->fTypes.fFloat4);
926 skvm::Color dstColor = {f32(argVal[0]), f32(argVal[1]), f32(argVal[2]), f32(argVal[3])};
927
928 color = fSampleBlender(child_it->second, srcColor, dstColor);
929 break;
930 }
931 default: {
932 SkDEBUGFAILF("cannot sample from type '%s'", c.child().type().description().c_str());
933 }
934 }
935
936 Value result(4);
937 result[0] = color.r;
938 result[1] = color.g;
939 result[2] = color.b;
940 result[3] = color.a;
941 return result;
942}
943
Brian Osman0a442b72020-12-02 11:12:51 -0500944Value SkVMGenerator::writeIntrinsicCall(const FunctionCall& c) {
John Stiles032fcba2021-05-06 11:33:08 -0400945 IntrinsicKind intrinsicKind = c.function().intrinsicKind();
946 SkASSERT(intrinsicKind != kNotIntrinsic);
Brian Osman0a442b72020-12-02 11:12:51 -0500947
948 const size_t nargs = c.arguments().size();
Brian Osman0a442b72020-12-02 11:12:51 -0500949 const size_t kMaxArgs = 3; // eg: clamp, mix, smoothstep
950 Value args[kMaxArgs];
951 SkASSERT(nargs >= 1 && nargs <= SK_ARRAY_COUNT(args));
952
953 // All other intrinsics have at most three args, and those can all be evaluated up front:
954 for (size_t i = 0; i < nargs; ++i) {
955 args[i] = this->writeExpression(*c.arguments()[i]);
956 }
957 Type::NumberKind nk = base_number_kind(c.arguments()[0]->type());
958
959 auto binary = [&](auto&& fn) {
960 // Binary intrinsics are (vecN, vecN), (vecN, float), or (float, vecN)
961 size_t nslots = std::max(args[0].slots(), args[1].slots());
962 Value result(nslots);
963 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
964 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
965
966 for (size_t i = 0; i < nslots; ++i) {
967 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
968 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]});
969 }
970 return result;
971 };
972
973 auto ternary = [&](auto&& fn) {
974 // Ternary intrinsics are some combination of vecN and float
975 size_t nslots = std::max({args[0].slots(), args[1].slots(), args[2].slots()});
976 Value result(nslots);
977 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
978 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
979 SkASSERT(args[2].slots() == nslots || args[2].slots() == 1);
980
981 for (size_t i = 0; i < nslots; ++i) {
982 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
983 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]},
984 {fBuilder, args[2][args[2].slots() == 1 ? 0 : i]});
985 }
986 return result;
987 };
988
989 auto dot = [&](const Value& x, const Value& y) {
990 SkASSERT(x.slots() == y.slots());
991 skvm::F32 result = f32(x[0]) * f32(y[0]);
992 for (size_t i = 1; i < x.slots(); ++i) {
993 result += f32(x[i]) * f32(y[i]);
994 }
995 return result;
996 };
997
John Stiles032fcba2021-05-06 11:33:08 -0400998 switch (intrinsicKind) {
999 case k_radians_IntrinsicKind:
Brian Osman22cc3be2020-12-30 10:38:15 -05001000 return unary(args[0], [](skvm::F32 deg) { return deg * (SK_FloatPI / 180); });
John Stiles032fcba2021-05-06 11:33:08 -04001001 case k_degrees_IntrinsicKind:
Brian Osman22cc3be2020-12-30 10:38:15 -05001002 return unary(args[0], [](skvm::F32 rad) { return rad * (180 / SK_FloatPI); });
1003
John Stiles032fcba2021-05-06 11:33:08 -04001004 case k_sin_IntrinsicKind: return unary(args[0], skvm::approx_sin);
1005 case k_cos_IntrinsicKind: return unary(args[0], skvm::approx_cos);
1006 case k_tan_IntrinsicKind: return unary(args[0], skvm::approx_tan);
Brian Osman0a442b72020-12-02 11:12:51 -05001007
John Stiles032fcba2021-05-06 11:33:08 -04001008 case k_asin_IntrinsicKind: return unary(args[0], skvm::approx_asin);
1009 case k_acos_IntrinsicKind: return unary(args[0], skvm::approx_acos);
Brian Osman0a442b72020-12-02 11:12:51 -05001010
John Stiles032fcba2021-05-06 11:33:08 -04001011 case k_atan_IntrinsicKind: return nargs == 1 ? unary(args[0], skvm::approx_atan)
Brian Osman0a442b72020-12-02 11:12:51 -05001012 : binary(skvm::approx_atan2);
1013
John Stiles032fcba2021-05-06 11:33:08 -04001014 case k_pow_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001015 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::approx_powf(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001016 case k_exp_IntrinsicKind: return unary(args[0], skvm::approx_exp);
1017 case k_log_IntrinsicKind: return unary(args[0], skvm::approx_log);
1018 case k_exp2_IntrinsicKind: return unary(args[0], skvm::approx_pow2);
1019 case k_log2_IntrinsicKind: return unary(args[0], skvm::approx_log2);
Brian Osman0a442b72020-12-02 11:12:51 -05001020
John Stiles032fcba2021-05-06 11:33:08 -04001021 case k_sqrt_IntrinsicKind: return unary(args[0], skvm::sqrt);
1022 case k_inversesqrt_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001023 return unary(args[0], [](skvm::F32 x) { return 1.0f / skvm::sqrt(x); });
1024
John Stiles032fcba2021-05-06 11:33:08 -04001025 case k_abs_IntrinsicKind: return unary(args[0], skvm::abs);
1026 case k_sign_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001027 return unary(args[0], [](skvm::F32 x) { return select(x < 0, -1.0f,
1028 select(x > 0, +1.0f, 0.0f)); });
John Stiles032fcba2021-05-06 11:33:08 -04001029 case k_floor_IntrinsicKind: return unary(args[0], skvm::floor);
1030 case k_ceil_IntrinsicKind: return unary(args[0], skvm::ceil);
1031 case k_fract_IntrinsicKind: return unary(args[0], skvm::fract);
1032 case k_mod_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001033 return binary([](skvm::F32 x, skvm::F32 y) { return x - y*skvm::floor(x / y); });
1034
John Stiles032fcba2021-05-06 11:33:08 -04001035 case k_min_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001036 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::min(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001037 case k_max_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001038 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::max(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001039 case k_clamp_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001040 return ternary(
1041 [](skvm::F32 x, skvm::F32 lo, skvm::F32 hi) { return skvm::clamp(x, lo, hi); });
John Stiles032fcba2021-05-06 11:33:08 -04001042 case k_saturate_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001043 return unary(args[0], [](skvm::F32 x) { return skvm::clamp01(x); });
John Stiles032fcba2021-05-06 11:33:08 -04001044 case k_mix_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001045 return ternary(
1046 [](skvm::F32 x, skvm::F32 y, skvm::F32 t) { return skvm::lerp(x, y, t); });
John Stiles032fcba2021-05-06 11:33:08 -04001047 case k_step_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001048 return binary([](skvm::F32 edge, skvm::F32 x) { return select(x < edge, 0.0f, 1.0f); });
John Stiles032fcba2021-05-06 11:33:08 -04001049 case k_smoothstep_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001050 return ternary([](skvm::F32 edge0, skvm::F32 edge1, skvm::F32 x) {
1051 skvm::F32 t = skvm::clamp01((x - edge0) / (edge1 - edge0));
Mike Kleinff4decc2021-02-10 16:13:35 -06001052 return t ** t ** (3 - 2 ** t);
Brian Osman0a442b72020-12-02 11:12:51 -05001053 });
1054
John Stiles032fcba2021-05-06 11:33:08 -04001055 case k_length_IntrinsicKind: return skvm::sqrt(dot(args[0], args[0]));
1056 case k_distance_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001057 Value vec = binary([](skvm::F32 x, skvm::F32 y) { return x - y; });
1058 return skvm::sqrt(dot(vec, vec));
1059 }
John Stiles032fcba2021-05-06 11:33:08 -04001060 case k_dot_IntrinsicKind: return dot(args[0], args[1]);
1061 case k_cross_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001062 skvm::F32 ax = f32(args[0][0]), ay = f32(args[0][1]), az = f32(args[0][2]),
1063 bx = f32(args[1][0]), by = f32(args[1][1]), bz = f32(args[1][2]);
1064 Value result(3);
Mike Kleinff4decc2021-02-10 16:13:35 -06001065 result[0] = ay**bz - az**by;
1066 result[1] = az**bx - ax**bz;
1067 result[2] = ax**by - ay**bx;
Brian Osman22cc3be2020-12-30 10:38:15 -05001068 return result;
1069 }
John Stiles032fcba2021-05-06 11:33:08 -04001070 case k_normalize_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001071 skvm::F32 invLen = 1.0f / skvm::sqrt(dot(args[0], args[0]));
Mike Kleinff4decc2021-02-10 16:13:35 -06001072 return unary(args[0], [&](skvm::F32 x) { return x ** invLen; });
Brian Osman0a442b72020-12-02 11:12:51 -05001073 }
John Stiles032fcba2021-05-06 11:33:08 -04001074 case k_faceforward_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001075 const Value &N = args[0],
1076 &I = args[1],
1077 &Nref = args[2];
1078
1079 skvm::F32 dotNrefI = dot(Nref, I);
1080 return unary(N, [&](skvm::F32 n) { return select(dotNrefI<0, n, -n); });
1081 }
John Stiles032fcba2021-05-06 11:33:08 -04001082 case k_reflect_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001083 const Value &I = args[0],
1084 &N = args[1];
1085
1086 skvm::F32 dotNI = dot(N, I);
1087 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001088 return i - 2**dotNI**n;
Brian Osman22cc3be2020-12-30 10:38:15 -05001089 });
1090 }
John Stiles032fcba2021-05-06 11:33:08 -04001091 case k_refract_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001092 const Value &I = args[0],
1093 &N = args[1];
1094 skvm::F32 eta = f32(args[2]);
1095
1096 skvm::F32 dotNI = dot(N, I),
Mike Kleinff4decc2021-02-10 16:13:35 -06001097 k = 1 - eta**eta**(1 - dotNI**dotNI);
Brian Osman22cc3be2020-12-30 10:38:15 -05001098 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001099 return select(k<0, 0.0f, eta**i - (eta**dotNI + sqrt(k))**n);
Brian Osman22cc3be2020-12-30 10:38:15 -05001100 });
1101 }
Brian Osman0a442b72020-12-02 11:12:51 -05001102
John Stiles032fcba2021-05-06 11:33:08 -04001103 case k_matrixCompMult_IntrinsicKind:
Mike Kleinff4decc2021-02-10 16:13:35 -06001104 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; });
John Stiles032fcba2021-05-06 11:33:08 -04001105 case k_inverse_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001106 switch (args[0].slots()) {
1107 case 4: return this->writeMatrixInverse2x2(args[0]);
1108 case 9: return this->writeMatrixInverse3x3(args[0]);
1109 case 16: return this->writeMatrixInverse4x4(args[0]);
1110 default:
1111 SkDEBUGFAIL("Invalid call to inverse");
1112 return {};
1113 }
1114 }
1115
John Stiles032fcba2021-05-06 11:33:08 -04001116 case k_lessThan_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001117 return nk == Type::NumberKind::kFloat
1118 ? binary([](skvm::F32 x, skvm::F32 y) { return x < y; })
1119 : binary([](skvm::I32 x, skvm::I32 y) { return x < y; });
John Stiles032fcba2021-05-06 11:33:08 -04001120 case k_lessThanEqual_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001121 return nk == Type::NumberKind::kFloat
1122 ? binary([](skvm::F32 x, skvm::F32 y) { return x <= y; })
1123 : binary([](skvm::I32 x, skvm::I32 y) { return x <= y; });
John Stiles032fcba2021-05-06 11:33:08 -04001124 case k_greaterThan_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001125 return nk == Type::NumberKind::kFloat
1126 ? binary([](skvm::F32 x, skvm::F32 y) { return x > y; })
1127 : binary([](skvm::I32 x, skvm::I32 y) { return x > y; });
John Stiles032fcba2021-05-06 11:33:08 -04001128 case k_greaterThanEqual_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001129 return nk == Type::NumberKind::kFloat
1130 ? binary([](skvm::F32 x, skvm::F32 y) { return x >= y; })
1131 : binary([](skvm::I32 x, skvm::I32 y) { return x >= y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001132
John Stiles032fcba2021-05-06 11:33:08 -04001133 case k_equal_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001134 return nk == Type::NumberKind::kFloat
1135 ? binary([](skvm::F32 x, skvm::F32 y) { return x == y; })
1136 : binary([](skvm::I32 x, skvm::I32 y) { return x == y; });
John Stiles032fcba2021-05-06 11:33:08 -04001137 case k_notEqual_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001138 return nk == Type::NumberKind::kFloat
1139 ? binary([](skvm::F32 x, skvm::F32 y) { return x != y; })
1140 : binary([](skvm::I32 x, skvm::I32 y) { return x != y; });
1141
John Stiles032fcba2021-05-06 11:33:08 -04001142 case k_any_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001143 skvm::I32 result = i32(args[0][0]);
1144 for (size_t i = 1; i < args[0].slots(); ++i) {
1145 result |= i32(args[0][i]);
1146 }
1147 return result;
1148 }
John Stiles032fcba2021-05-06 11:33:08 -04001149 case k_all_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001150 skvm::I32 result = i32(args[0][0]);
1151 for (size_t i = 1; i < args[0].slots(); ++i) {
1152 result &= i32(args[0][i]);
1153 }
1154 return result;
1155 }
John Stiles032fcba2021-05-06 11:33:08 -04001156 case k_not_IntrinsicKind: return unary(args[0], [](skvm::I32 x) { return ~x; });
Brian Osman0a442b72020-12-02 11:12:51 -05001157
John Stiles032fcba2021-05-06 11:33:08 -04001158 default:
1159 SkDEBUGFAILF("unsupported intrinsic %s", c.function().description().c_str());
Brian Osman0a442b72020-12-02 11:12:51 -05001160 return {};
1161 }
1162 SkUNREACHABLE;
1163}
1164
1165Value SkVMGenerator::writeFunctionCall(const FunctionCall& f) {
John Stiles032fcba2021-05-06 11:33:08 -04001166 if (f.function().isIntrinsic() && !f.function().definition()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001167 return this->writeIntrinsicCall(f);
1168 }
1169
Brian Osman54515b72021-01-07 14:38:08 -05001170 const FunctionDeclaration& decl = f.function();
1171
1172 // Evaluate all arguments, gather the results into a contiguous list of IDs
1173 std::vector<skvm::Val> argVals;
1174 for (const auto& arg : f.arguments()) {
1175 Value v = this->writeExpression(*arg);
1176 for (size_t i = 0; i < v.slots(); ++i) {
1177 argVals.push_back(v[i]);
1178 }
1179 }
1180
1181 // Create storage for the return value
John Stiles727adfe2021-09-14 14:07:23 -04001182 const skvm::F32 zero = fBuilder->splat(0.0f);
John Stiles47b087e2021-04-06 13:19:35 -04001183 size_t nslots = f.type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001184 Value result(nslots);
1185 for (size_t i = 0; i < nslots; ++i) {
John Stiles727adfe2021-09-14 14:07:23 -04001186 result[i] = zero;
Brian Osman54515b72021-01-07 14:38:08 -05001187 }
1188
1189 {
Brian Osman9333c872021-01-13 15:06:17 -05001190 // This merges currentFunction().fReturned into fConditionMask. Lanes that conditionally
Brian Osman54515b72021-01-07 14:38:08 -05001191 // returned in the current function would otherwise resume execution within the child.
Brian Osman9333c872021-01-13 15:06:17 -05001192 ScopedCondition m(this, ~currentFunction().fReturned);
Ethan Nicholas624a5292021-04-16 14:54:43 -04001193 SkASSERTF(f.function().definition(), "no definition for function '%s'",
1194 f.function().description().c_str());
Brian Osmanae87bf12021-05-11 13:36:10 -04001195 this->writeFunction(*f.function().definition(), SkMakeSpan(argVals), result.asSpan());
Brian Osman54515b72021-01-07 14:38:08 -05001196 }
1197
1198 // Propagate new values of any 'out' params back to the original arguments
1199 const std::unique_ptr<Expression>* argIter = f.arguments().begin();
1200 size_t valIdx = 0;
1201 for (const Variable* p : decl.parameters()) {
John Stiles68f56062021-08-03 12:31:56 -04001202 nslots = p->type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001203 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1204 Value v(nslots);
1205 for (size_t i = 0; i < nslots; ++i) {
1206 v[i] = argVals[valIdx + i];
1207 }
1208 const std::unique_ptr<Expression>& arg = *argIter;
1209 this->writeStore(*arg, v);
1210 }
1211 valIdx += nslots;
1212 argIter++;
1213 }
1214
1215 return result;
Brian Osman0a442b72020-12-02 11:12:51 -05001216}
1217
Brian Osmandd50b0c2021-01-11 17:04:29 -05001218Value SkVMGenerator::writeExternalFunctionCall(const ExternalFunctionCall& c) {
1219 // Evaluate all arguments, gather the results into a contiguous list of F32
1220 std::vector<skvm::F32> args;
1221 for (const auto& arg : c.arguments()) {
1222 Value v = this->writeExpression(*arg);
1223 for (size_t i = 0; i < v.slots(); ++i) {
1224 args.push_back(f32(v[i]));
1225 }
1226 }
1227
1228 // Create storage for the return value
John Stiles47b087e2021-04-06 13:19:35 -04001229 size_t nslots = c.type().slotCount();
Brian Osmandd50b0c2021-01-11 17:04:29 -05001230 std::vector<skvm::F32> result(nslots, fBuilder->splat(0.0f));
1231
1232 c.function().call(fBuilder, args.data(), result.data(), this->mask());
1233
1234 // Convert from 'vector of F32' to Value
1235 Value resultVal(nslots);
1236 for (size_t i = 0; i < nslots; ++i) {
1237 resultVal[i] = result[i];
1238 }
1239
1240 return resultVal;
1241}
1242
John Stiles7591d4b2021-09-13 13:32:06 -04001243Value SkVMGenerator::writeLiteral(const Literal& l) {
1244 if (l.type().isFloat()) {
1245 return fBuilder->splat(l.as<Literal>().floatValue());
1246 }
1247 if (l.type().isInteger()) {
1248 return fBuilder->splat(static_cast<int>(l.as<Literal>().intValue()));
1249 }
1250 SkASSERT(l.type().isBoolean());
1251 return fBuilder->splat(l.as<Literal>().boolValue() ? ~0 : 0);
1252}
1253
Brian Osman0a442b72020-12-02 11:12:51 -05001254Value SkVMGenerator::writePrefixExpression(const PrefixExpression& p) {
1255 Value val = this->writeExpression(*p.operand());
1256
John Stiles45990502021-02-16 10:55:27 -05001257 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001258 case Token::Kind::TK_PLUSPLUS:
1259 case Token::Kind::TK_MINUSMINUS: {
John Stiles45990502021-02-16 10:55:27 -05001260 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001261
1262 switch (base_number_kind(p.type())) {
1263 case Type::NumberKind::kFloat:
1264 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1265 break;
1266 case Type::NumberKind::kSigned:
1267 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1268 break;
1269 default:
1270 SkASSERT(false);
1271 return {};
1272 }
1273 return this->writeStore(*p.operand(), val);
1274 }
1275 case Token::Kind::TK_MINUS: {
1276 switch (base_number_kind(p.type())) {
1277 case Type::NumberKind::kFloat:
1278 return this->unary(val, [](skvm::F32 x) { return -x; });
1279 case Type::NumberKind::kSigned:
1280 return this->unary(val, [](skvm::I32 x) { return -x; });
1281 default:
1282 SkASSERT(false);
1283 return {};
1284 }
1285 }
1286 case Token::Kind::TK_LOGICALNOT:
1287 case Token::Kind::TK_BITWISENOT:
1288 return this->unary(val, [](skvm::I32 x) { return ~x; });
1289 default:
1290 SkASSERT(false);
1291 return {};
1292 }
1293}
1294
1295Value SkVMGenerator::writePostfixExpression(const PostfixExpression& p) {
John Stiles45990502021-02-16 10:55:27 -05001296 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001297 case Token::Kind::TK_PLUSPLUS:
1298 case Token::Kind::TK_MINUSMINUS: {
1299 Value old = this->writeExpression(*p.operand()),
1300 val = old;
1301 SkASSERT(val.slots() == 1);
John Stiles45990502021-02-16 10:55:27 -05001302 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001303
1304 switch (base_number_kind(p.type())) {
1305 case Type::NumberKind::kFloat:
1306 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1307 break;
1308 case Type::NumberKind::kSigned:
1309 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1310 break;
1311 default:
1312 SkASSERT(false);
1313 return {};
1314 }
1315 this->writeStore(*p.operand(), val);
1316 return old;
1317 }
1318 default:
1319 SkASSERT(false);
1320 return {};
1321 }
1322}
1323
1324Value SkVMGenerator::writeSwizzle(const Swizzle& s) {
1325 Value base = this->writeExpression(*s.base());
1326 Value swizzled(s.components().size());
1327 for (size_t i = 0; i < s.components().size(); ++i) {
1328 swizzled[i] = base[s.components()[i]];
1329 }
1330 return swizzled;
1331}
1332
1333Value SkVMGenerator::writeTernaryExpression(const TernaryExpression& t) {
1334 skvm::I32 test = i32(this->writeExpression(*t.test()));
1335 Value ifTrue, ifFalse;
1336
1337 {
Brian Osman9333c872021-01-13 15:06:17 -05001338 ScopedCondition m(this, test);
Brian Osman0a442b72020-12-02 11:12:51 -05001339 ifTrue = this->writeExpression(*t.ifTrue());
1340 }
1341 {
Brian Osman9333c872021-01-13 15:06:17 -05001342 ScopedCondition m(this, ~test);
Brian Osman0a442b72020-12-02 11:12:51 -05001343 ifFalse = this->writeExpression(*t.ifFalse());
1344 }
1345
1346 size_t nslots = ifTrue.slots();
1347 SkASSERT(nslots == ifFalse.slots());
1348
1349 Value result(nslots);
1350 for (size_t i = 0; i < nslots; ++i) {
1351 result[i] = skvm::select(test, i32(ifTrue[i]), i32(ifFalse[i]));
1352 }
1353 return result;
1354}
1355
1356Value SkVMGenerator::writeExpression(const Expression& e) {
1357 switch (e.kind()) {
1358 case Expression::Kind::kBinary:
1359 return this->writeBinaryExpression(e.as<BinaryExpression>());
Brian Osmaneb0f29d2021-08-04 11:34:16 -04001360 case Expression::Kind::kChildCall:
1361 return this->writeChildCall(e.as<ChildCall>());
John Stiles7384b372021-04-01 13:48:15 -04001362 case Expression::Kind::kConstructorArray:
John Stiles8cad6372021-04-07 12:31:13 -04001363 case Expression::Kind::kConstructorCompound:
John Stilesd47330f2021-04-08 23:25:52 -04001364 case Expression::Kind::kConstructorStruct:
John Stilesd986f472021-04-06 15:54:43 -04001365 return this->writeAggregationConstructor(e.asAnyConstructor());
John Stilese3ae9682021-08-05 10:35:01 -04001366 case Expression::Kind::kConstructorArrayCast:
1367 return this->writeExpression(*e.as<ConstructorArrayCast>().argument());
John Stilese1182782021-03-30 22:09:37 -04001368 case Expression::Kind::kConstructorDiagonalMatrix:
1369 return this->writeConstructorDiagonalMatrix(e.as<ConstructorDiagonalMatrix>());
John Stiles5abb9e12021-04-06 13:47:19 -04001370 case Expression::Kind::kConstructorMatrixResize:
1371 return this->writeConstructorMatrixResize(e.as<ConstructorMatrixResize>());
John Stilesfd7252f2021-04-04 22:24:40 -04001372 case Expression::Kind::kConstructorScalarCast:
John Stiles8cad6372021-04-07 12:31:13 -04001373 case Expression::Kind::kConstructorCompoundCast:
John Stilesb14a8192021-04-05 11:40:46 -04001374 return this->writeConstructorCast(e.asAnyConstructor());
John Stiles2938eea2021-04-01 18:58:25 -04001375 case Expression::Kind::kConstructorSplat:
1376 return this->writeConstructorSplat(e.as<ConstructorSplat>());
Brian Osman0a442b72020-12-02 11:12:51 -05001377 case Expression::Kind::kFieldAccess:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001378 return this->writeFieldAccess(e.as<FieldAccess>());
Brian Osman0a442b72020-12-02 11:12:51 -05001379 case Expression::Kind::kIndex:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001380 return this->writeIndexExpression(e.as<IndexExpression>());
Brian Osman0a442b72020-12-02 11:12:51 -05001381 case Expression::Kind::kVariableReference:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001382 return this->writeVariableExpression(e.as<VariableReference>());
John Stiles7591d4b2021-09-13 13:32:06 -04001383 case Expression::Kind::kLiteral:
1384 return this->writeLiteral(e.as<Literal>());
Brian Osman0a442b72020-12-02 11:12:51 -05001385 case Expression::Kind::kFunctionCall:
1386 return this->writeFunctionCall(e.as<FunctionCall>());
Brian Osmandd50b0c2021-01-11 17:04:29 -05001387 case Expression::Kind::kExternalFunctionCall:
1388 return this->writeExternalFunctionCall(e.as<ExternalFunctionCall>());
Brian Osman0a442b72020-12-02 11:12:51 -05001389 case Expression::Kind::kPrefix:
1390 return this->writePrefixExpression(e.as<PrefixExpression>());
1391 case Expression::Kind::kPostfix:
1392 return this->writePostfixExpression(e.as<PostfixExpression>());
1393 case Expression::Kind::kSwizzle:
1394 return this->writeSwizzle(e.as<Swizzle>());
1395 case Expression::Kind::kTernary:
1396 return this->writeTernaryExpression(e.as<TernaryExpression>());
Brian Osmanbe0b3b72021-01-06 14:27:35 -05001397 case Expression::Kind::kExternalFunctionReference:
Brian Osman0a442b72020-12-02 11:12:51 -05001398 default:
1399 SkDEBUGFAIL("Unsupported expression");
1400 return {};
1401 }
1402}
1403
1404Value SkVMGenerator::writeStore(const Expression& lhs, const Value& rhs) {
John Stiles47b087e2021-04-06 13:19:35 -04001405 SkASSERTF(rhs.slots() == lhs.type().slotCount(),
John Stiles7bf79992021-06-25 11:05:20 -04001406 "lhs=%s (%s)\nrhs=%zu slot",
John Stiles94e72b92021-01-30 11:06:18 -05001407 lhs.type().description().c_str(), lhs.description().c_str(), rhs.slots());
Brian Osman0a442b72020-12-02 11:12:51 -05001408
Brian Osman21f57072021-01-25 13:51:57 -05001409 // We need to figure out the collection of slots that we're storing into. The l-value (lhs)
1410 // is always a VariableReference, possibly wrapped by one or more Swizzle, FieldAccess, or
1411 // IndexExpressions. The underlying VariableReference has a range of slots for its storage,
1412 // and each expression wrapped around that selects a sub-set of those slots (Field/Index),
1413 // or rearranges them (Swizzle).
1414 SkSTArray<4, size_t, true> slots;
1415 slots.resize(rhs.slots());
1416
1417 // Start with the identity slot map - this basically says that the values from rhs belong in
1418 // slots [0, 1, 2 ... N] of the lhs.
1419 for (size_t i = 0; i < slots.size(); ++i) {
1420 slots[i] = i;
1421 }
1422
1423 // Now, as we peel off each outer expression, adjust 'slots' to be the locations relative to
1424 // the next (inner) expression:
1425 const Expression* expr = &lhs;
1426 while (!expr->is<VariableReference>()) {
1427 switch (expr->kind()) {
1428 case Expression::Kind::kFieldAccess: {
1429 const FieldAccess& fld = expr->as<FieldAccess>();
1430 size_t offset = this->fieldSlotOffset(fld);
1431 for (size_t& s : slots) {
1432 s += offset;
1433 }
1434 expr = fld.base().get();
1435 } break;
1436 case Expression::Kind::kIndex: {
1437 const IndexExpression& idx = expr->as<IndexExpression>();
1438 size_t offset = this->indexSlotOffset(idx);
1439 for (size_t& s : slots) {
1440 s += offset;
1441 }
1442 expr = idx.base().get();
1443 } break;
1444 case Expression::Kind::kSwizzle: {
1445 const Swizzle& swz = expr->as<Swizzle>();
1446 for (size_t& s : slots) {
1447 s = swz.components()[s];
1448 }
1449 expr = swz.base().get();
1450 } break;
1451 default:
1452 // No other kinds of expressions are valid in lvalues. (see Analysis::IsAssignable)
1453 SkDEBUGFAIL("Invalid expression type");
1454 return {};
1455 }
1456 }
1457
1458 // When we get here, 'slots' are all relative to the first slot holding 'var's storage
1459 const Variable& var = *expr->as<VariableReference>().variable();
1460 size_t varSlot = this->getSlot(var);
John Stilescb400082021-09-23 11:07:32 -04001461 for (size_t& slot : slots) {
1462 SkASSERT(slot < var.type().slotCount());
1463 slot += varSlot;
1464 }
1465
1466 // `slots` are now absolute indices into `fSlots`.
1467 this->writeStore(SkMakeSpan(slots), rhs);
1468 return rhs;
1469}
1470
1471void SkVMGenerator::writeStore(SkSpan<size_t> slots, const Value& rhs) {
1472 SkASSERT(rhs.slots() == slots.size());
1473
Brian Osman0a442b72020-12-02 11:12:51 -05001474 skvm::I32 mask = this->mask();
1475 for (size_t i = rhs.slots(); i --> 0;) {
John Stilescb400082021-09-23 11:07:32 -04001476 skvm::F32 curr = f32(fSlots[slots[i]]),
Brian Osman0a442b72020-12-02 11:12:51 -05001477 next = f32(rhs[i]);
John Stilescb400082021-09-23 11:07:32 -04001478 fSlots[slots[i]] = select(mask, next, curr).id;
Brian Osman0a442b72020-12-02 11:12:51 -05001479 }
Brian Osman0a442b72020-12-02 11:12:51 -05001480}
1481
1482void SkVMGenerator::writeBlock(const Block& b) {
1483 for (const std::unique_ptr<Statement>& stmt : b.children()) {
1484 this->writeStatement(*stmt);
1485 }
1486}
1487
Brian Osman9333c872021-01-13 15:06:17 -05001488void SkVMGenerator::writeBreakStatement() {
1489 // Any active lanes stop executing for the duration of the current loop
1490 fLoopMask &= ~this->mask();
1491}
1492
1493void SkVMGenerator::writeContinueStatement() {
1494 // Any active lanes stop executing for the current iteration.
1495 // Remember them in fContinueMask, to be re-enabled later.
1496 skvm::I32 mask = this->mask();
1497 fLoopMask &= ~mask;
1498 fContinueMask |= mask;
1499}
1500
1501void SkVMGenerator::writeForStatement(const ForStatement& f) {
1502 // We require that all loops be ES2-compliant (unrollable), and actually unroll them here
John Stiles9c975c52021-08-31 10:18:57 -04001503 SkASSERT(f.unrollInfo());
1504 const LoopUnrollInfo& loop = *f.unrollInfo();
John Stiles47b087e2021-04-06 13:19:35 -04001505 SkASSERT(loop.fIndex->type().slotCount() == 1);
Brian Osman9333c872021-01-13 15:06:17 -05001506
Brian Osman21f57072021-01-25 13:51:57 -05001507 size_t indexSlot = this->getSlot(*loop.fIndex);
Brian Osman9333c872021-01-13 15:06:17 -05001508 double val = loop.fStart;
1509
John Stiles727adfe2021-09-14 14:07:23 -04001510 const skvm::I32 zero = fBuilder->splat(0);
Brian Osman9333c872021-01-13 15:06:17 -05001511 skvm::I32 oldLoopMask = fLoopMask,
1512 oldContinueMask = fContinueMask;
1513
1514 for (int i = 0; i < loop.fCount; ++i) {
Brian Osman21f57072021-01-25 13:51:57 -05001515 fSlots[indexSlot] = loop.fIndex->type().isInteger()
1516 ? fBuilder->splat(static_cast<int>(val)).id
1517 : fBuilder->splat(static_cast<float>(val)).id;
Brian Osman9333c872021-01-13 15:06:17 -05001518
John Stiles727adfe2021-09-14 14:07:23 -04001519 fContinueMask = zero;
Brian Osman9333c872021-01-13 15:06:17 -05001520 this->writeStatement(*f.statement());
1521 fLoopMask |= fContinueMask;
1522
1523 val += loop.fDelta;
1524 }
1525
1526 fLoopMask = oldLoopMask;
1527 fContinueMask = oldContinueMask;
1528}
1529
Brian Osman0a442b72020-12-02 11:12:51 -05001530void SkVMGenerator::writeIfStatement(const IfStatement& i) {
1531 Value test = this->writeExpression(*i.test());
1532 {
Brian Osman9333c872021-01-13 15:06:17 -05001533 ScopedCondition ifTrue(this, i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001534 this->writeStatement(*i.ifTrue());
1535 }
1536 if (i.ifFalse()) {
Brian Osman9333c872021-01-13 15:06:17 -05001537 ScopedCondition ifFalse(this, ~i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001538 this->writeStatement(*i.ifFalse());
1539 }
1540}
1541
1542void SkVMGenerator::writeReturnStatement(const ReturnStatement& r) {
Brian Osman54515b72021-01-07 14:38:08 -05001543 skvm::I32 returnsHere = this->mask();
Brian Osman0a442b72020-12-02 11:12:51 -05001544
Brian Osman54515b72021-01-07 14:38:08 -05001545 if (r.expression()) {
1546 Value val = this->writeExpression(*r.expression());
Brian Osman0a442b72020-12-02 11:12:51 -05001547
Brian Osman54515b72021-01-07 14:38:08 -05001548 int i = 0;
1549 for (skvm::Val& slot : currentFunction().fReturnValue) {
1550 slot = select(returnsHere, f32(val[i]), f32(slot)).id;
1551 i++;
1552 }
Brian Osman0a442b72020-12-02 11:12:51 -05001553 }
1554
Brian Osman54515b72021-01-07 14:38:08 -05001555 currentFunction().fReturned |= returnsHere;
Brian Osman0a442b72020-12-02 11:12:51 -05001556}
1557
John Stilescb400082021-09-23 11:07:32 -04001558void SkVMGenerator::writeSwitchStatement(const SwitchStatement& s) {
1559 skvm::Val falseValue = fBuilder->splat( 0).id;
1560 skvm::Val trueValue = fBuilder->splat(~0).id;
1561
1562 // Create a new slot for the "switchFallthough" scratch variable, initialized to false.
1563 size_t switchFallthroughSlot = fSlots.size();
1564 fSlots.push_back(falseValue);
1565
1566 // Loop masks behave just like for statements. When a break is encountered, it masks off all
1567 // lanes for the rest of the body of the switch.
1568 skvm::I32 oldLoopMask = fLoopMask;
1569 Value switchValue = this->writeExpression(*s.value());
1570
1571 for (const std::unique_ptr<Statement>& stmt : s.cases()) {
1572 const SwitchCase& c = stmt->as<SwitchCase>();
1573 if (c.value()) {
1574 Value caseValue = this->writeExpression(*c.value());
1575
1576 // We want to execute this switch case if we're falling through from a previous case, or
1577 // if the case value matches.
1578 Value switchFallthroughValue(1);
1579 switchFallthroughValue[0] = fSlots[switchFallthroughSlot];
1580
1581 Value condition = i32(switchFallthroughValue) | (i32(caseValue) == i32(switchValue));
1582 ScopedCondition conditionalCaseBlock(this, i32(condition));
1583 this->writeStatement(*c.statement());
1584
1585 // We always set the fallthrough flag after a case block (`break` still works to stop
1586 // the flow of execution regardless).
1587 this->writeStore(SkMakeSpan(&switchFallthroughSlot, 1), i32(trueValue));
1588 } else {
1589 // This is the default case. Since it's always last, we can just dump in the code.
1590 this->writeStatement(*c.statement());
1591 }
1592 }
1593
1594 // Restore state.
1595 fLoopMask = oldLoopMask;
1596 fSlots.pop_back();
1597}
1598
Brian Osman0a442b72020-12-02 11:12:51 -05001599void SkVMGenerator::writeVarDeclaration(const VarDeclaration& decl) {
Brian Osman21f57072021-01-25 13:51:57 -05001600 size_t slot = this->getSlot(decl.var()),
John Stiles47b087e2021-04-06 13:19:35 -04001601 nslots = decl.var().type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -05001602
1603 Value val = decl.value() ? this->writeExpression(*decl.value()) : Value{};
1604 for (size_t i = 0; i < nslots; ++i) {
1605 fSlots[slot + i] = val ? val[i] : fBuilder->splat(0.0f).id;
1606 }
1607}
1608
1609void SkVMGenerator::writeStatement(const Statement& s) {
1610 switch (s.kind()) {
1611 case Statement::Kind::kBlock:
1612 this->writeBlock(s.as<Block>());
1613 break;
Brian Osman9333c872021-01-13 15:06:17 -05001614 case Statement::Kind::kBreak:
1615 this->writeBreakStatement();
1616 break;
1617 case Statement::Kind::kContinue:
1618 this->writeContinueStatement();
1619 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001620 case Statement::Kind::kExpression:
1621 this->writeExpression(*s.as<ExpressionStatement>().expression());
1622 break;
Brian Osman9333c872021-01-13 15:06:17 -05001623 case Statement::Kind::kFor:
1624 this->writeForStatement(s.as<ForStatement>());
1625 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001626 case Statement::Kind::kIf:
1627 this->writeIfStatement(s.as<IfStatement>());
1628 break;
1629 case Statement::Kind::kReturn:
1630 this->writeReturnStatement(s.as<ReturnStatement>());
1631 break;
John Stilescb400082021-09-23 11:07:32 -04001632 case Statement::Kind::kSwitch:
1633 this->writeSwitchStatement(s.as<SwitchStatement>());
1634 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001635 case Statement::Kind::kVarDeclaration:
1636 this->writeVarDeclaration(s.as<VarDeclaration>());
1637 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001638 case Statement::Kind::kDiscard:
1639 case Statement::Kind::kDo:
Brian Osman57e353f2021-01-07 15:55:20 -05001640 SkDEBUGFAIL("Unsupported control flow");
Brian Osman0a442b72020-12-02 11:12:51 -05001641 break;
1642 case Statement::Kind::kInlineMarker:
1643 case Statement::Kind::kNop:
1644 break;
1645 default:
1646 SkASSERT(false);
1647 }
1648}
1649
1650skvm::Color ProgramToSkVM(const Program& program,
1651 const FunctionDefinition& function,
1652 skvm::Builder* builder,
1653 SkSpan<skvm::Val> uniforms,
1654 skvm::Coord device,
1655 skvm::Coord local,
Brian Osman577c6062021-04-12 17:17:19 -04001656 skvm::Color inputColor,
John Stiles50d0d092021-06-09 17:24:31 -04001657 skvm::Color destColor,
John Stiles137482f2021-07-23 10:38:57 -04001658 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -04001659 SampleColorFilterFn sampleColorFilter,
1660 SampleBlenderFn sampleBlender) {
Mike Kleinaebcf732021-01-14 10:15:00 -06001661 skvm::Val zero = builder->splat(0.0f).id;
1662 skvm::Val result[4] = {zero,zero,zero,zero};
Brian Osman577c6062021-04-12 17:17:19 -04001663
John Stilesf7f36ae2021-06-08 14:06:22 -04001664 skvm::Val args[8]; // At most 8 arguments (half4 srcColor, half4 dstColor)
Brian Osman577c6062021-04-12 17:17:19 -04001665 size_t argSlots = 0;
Brian Osman0a442b72020-12-02 11:12:51 -05001666 for (const SkSL::Variable* param : function.declaration().parameters()) {
Brian Osman577c6062021-04-12 17:17:19 -04001667 switch (param->modifiers().fLayout.fBuiltin) {
1668 case SK_MAIN_COORDS_BUILTIN:
1669 SkASSERT(param->type().slotCount() == 2);
John Stilesf7f36ae2021-06-08 14:06:22 -04001670 SkASSERT((argSlots + 2) <= SK_ARRAY_COUNT(args));
Brian Osman577c6062021-04-12 17:17:19 -04001671 args[argSlots++] = local.x.id;
1672 args[argSlots++] = local.y.id;
1673 break;
1674 case SK_INPUT_COLOR_BUILTIN:
1675 SkASSERT(param->type().slotCount() == 4);
John Stilesf7f36ae2021-06-08 14:06:22 -04001676 SkASSERT((argSlots + 4) <= SK_ARRAY_COUNT(args));
Brian Osman577c6062021-04-12 17:17:19 -04001677 args[argSlots++] = inputColor.r.id;
1678 args[argSlots++] = inputColor.g.id;
1679 args[argSlots++] = inputColor.b.id;
1680 args[argSlots++] = inputColor.a.id;
1681 break;
John Stiles50d0d092021-06-09 17:24:31 -04001682 case SK_DEST_COLOR_BUILTIN:
1683 SkASSERT(param->type().slotCount() == 4);
1684 SkASSERT((argSlots + 4) <= SK_ARRAY_COUNT(args));
1685 args[argSlots++] = destColor.r.id;
1686 args[argSlots++] = destColor.g.id;
1687 args[argSlots++] = destColor.b.id;
1688 args[argSlots++] = destColor.a.id;
1689 break;
Brian Osman577c6062021-04-12 17:17:19 -04001690 default:
1691 SkDEBUGFAIL("Invalid parameter to main()");
1692 return {};
1693 }
Brian Osman0a442b72020-12-02 11:12:51 -05001694 }
Brian Osman577c6062021-04-12 17:17:19 -04001695 SkASSERT(argSlots <= SK_ARRAY_COUNT(args));
Brian Osman0a442b72020-12-02 11:12:51 -05001696
John Stiles428af4c2021-09-22 14:28:19 -04001697 SkVMGenerator generator(program, builder, std::move(sampleShader),
John Stiles2955c262021-07-23 15:51:05 -04001698 std::move(sampleColorFilter), std::move(sampleBlender));
John Stilesa4f56832021-09-22 14:22:33 -04001699 generator.writeProgram(uniforms, device, function, {args, argSlots}, SkMakeSpan(result));
Brian Osman0a442b72020-12-02 11:12:51 -05001700
Brian Osman57e353f2021-01-07 15:55:20 -05001701 return skvm::Color{{builder, result[0]},
1702 {builder, result[1]},
1703 {builder, result[2]},
1704 {builder, result[3]}};
Brian Osman0a442b72020-12-02 11:12:51 -05001705}
1706
Brian Osmanf4a77732020-12-28 09:03:00 -05001707bool ProgramToSkVM(const Program& program,
1708 const FunctionDefinition& function,
1709 skvm::Builder* b,
Brian Osmanc92df392021-01-11 13:16:28 -05001710 SkSpan<skvm::Val> uniforms,
Brian Osmanf4a77732020-12-28 09:03:00 -05001711 SkVMSignature* outSignature) {
Brian Osmanf4a77732020-12-28 09:03:00 -05001712 SkVMSignature ignored,
1713 *signature = outSignature ? outSignature : &ignored;
1714
Mike Klein00e43df2021-01-08 13:45:42 -06001715 std::vector<skvm::Ptr> argPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001716 std::vector<skvm::Val> argVals;
1717
1718 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001719 size_t slots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001720 signature->fParameterSlots += slots;
1721 for (size_t i = 0; i < slots; ++i) {
1722 argPtrs.push_back(b->varying<float>());
1723 argVals.push_back(b->loadF(argPtrs.back()).id);
1724 }
1725 }
1726
Mike Klein00e43df2021-01-08 13:45:42 -06001727 std::vector<skvm::Ptr> returnPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001728 std::vector<skvm::Val> returnVals;
1729
John Stiles47b087e2021-04-06 13:19:35 -04001730 signature->fReturnSlots = function.declaration().returnType().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001731 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1732 returnPtrs.push_back(b->varying<float>());
1733 returnVals.push_back(b->splat(0.0f).id);
1734 }
1735
Brian Osmana8b897b2021-08-30 16:40:44 -04001736 bool sampledChildEffects = false;
1737 auto sampleShader = [&](int, skvm::Coord) {
1738 sampledChildEffects = true;
1739 return skvm::Color{};
1740 };
1741 auto sampleColorFilter = [&](int, skvm::Color) {
1742 sampledChildEffects = true;
1743 return skvm::Color{};
1744 };
1745 auto sampleBlender = [&](int, skvm::Color, skvm::Color) {
1746 sampledChildEffects = true;
1747 return skvm::Color{};
1748 };
1749
Brian Osmanc9125aa2021-04-21 09:57:19 -04001750 skvm::F32 zero = b->splat(0.0f);
1751 skvm::Coord zeroCoord = {zero, zero};
John Stiles428af4c2021-09-22 14:28:19 -04001752 SkVMGenerator generator(program, b, sampleShader, sampleColorFilter, sampleBlender);
John Stilesa4f56832021-09-22 14:22:33 -04001753 generator.writeProgram(uniforms, /*device=*/zeroCoord,
1754 function, SkMakeSpan(argVals), SkMakeSpan(returnVals));
Brian Osmanf4a77732020-12-28 09:03:00 -05001755
Brian Osmana8b897b2021-08-30 16:40:44 -04001756 // If the SkSL tried to use any shader, colorFilter, or blender objects - we don't have a
1757 // mechanism (yet) for binding to those.
1758 if (sampledChildEffects) {
1759 return false;
1760 }
1761
Brian Osmanf4a77732020-12-28 09:03:00 -05001762 // generateCode has updated the contents of 'argVals' for any 'out' or 'inout' parameters.
1763 // Propagate those changes back to our varying buffers:
1764 size_t argIdx = 0;
1765 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001766 size_t nslots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001767 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1768 for (size_t i = 0; i < nslots; ++i) {
1769 b->storeF(argPtrs[argIdx + i], skvm::F32{b, argVals[argIdx + i]});
1770 }
1771 }
1772 argIdx += nslots;
1773 }
1774
1775 // It's also updated the contents of 'returnVals' with the return value of the entry point.
1776 // Store that as well:
1777 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1778 b->storeF(returnPtrs[i], skvm::F32{b, returnVals[i]});
1779 }
1780
1781 return true;
1782}
1783
Brian Osman5933d4c2021-01-05 13:02:20 -05001784const FunctionDefinition* Program_GetFunction(const Program& program, const char* function) {
1785 for (const ProgramElement* e : program.elements()) {
1786 if (e->is<FunctionDefinition>() &&
1787 e->as<FunctionDefinition>().declaration().name() == function) {
1788 return &e->as<FunctionDefinition>();
1789 }
1790 }
1791 return nullptr;
1792}
1793
Brian Osmane89d8ea2021-01-20 14:01:30 -05001794static void gather_uniforms(UniformInfo* info, const Type& type, const String& name) {
1795 switch (type.typeKind()) {
1796 case Type::TypeKind::kStruct:
1797 for (const auto& f : type.fields()) {
1798 gather_uniforms(info, *f.fType, name + "." + f.fName);
1799 }
1800 break;
1801 case Type::TypeKind::kArray:
1802 for (int i = 0; i < type.columns(); ++i) {
1803 gather_uniforms(info, type.componentType(),
1804 String::printf("%s[%d]", name.c_str(), i));
1805 }
1806 break;
1807 case Type::TypeKind::kScalar:
1808 case Type::TypeKind::kVector:
1809 case Type::TypeKind::kMatrix:
1810 info->fUniforms.push_back({name, base_number_kind(type), type.rows(), type.columns(),
1811 info->fUniformSlotCount});
1812 info->fUniformSlotCount += type.columns() * type.rows();
1813 break;
1814 default:
1815 break;
1816 }
1817}
1818
1819std::unique_ptr<UniformInfo> Program_GetUniformInfo(const Program& program) {
1820 auto info = std::make_unique<UniformInfo>();
1821 for (const ProgramElement* e : program.elements()) {
1822 if (!e->is<GlobalVarDeclaration>()) {
1823 continue;
1824 }
1825 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1826 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
1827 if (var.modifiers().fFlags & Modifiers::kUniform_Flag) {
Ethan Nicholasd2e09602021-06-10 11:21:59 -04001828 gather_uniforms(info.get(), var.type(), String(var.name()));
Brian Osmane89d8ea2021-01-20 14:01:30 -05001829 }
1830 }
1831 return info;
1832}
1833
Brian Osman47726a12020-12-17 16:02:08 -05001834/*
1835 * Testing utility function that emits program's "main" with a minimal harness. Used to create
1836 * representative skvm op sequences for SkSL tests.
1837 */
1838bool testingOnly_ProgramToSkVMShader(const Program& program, skvm::Builder* builder) {
Brian Osman5933d4c2021-01-05 13:02:20 -05001839 const SkSL::FunctionDefinition* main = Program_GetFunction(program, "main");
1840 if (!main) {
1841 return false;
1842 }
1843
Brian Osman47726a12020-12-17 16:02:08 -05001844 size_t uniformSlots = 0;
1845 int childSlots = 0;
1846 for (const SkSL::ProgramElement* e : program.elements()) {
Brian Osman47726a12020-12-17 16:02:08 -05001847 if (e->is<GlobalVarDeclaration>()) {
1848 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1849 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
Brian Osman14d00962021-04-02 17:04:35 -04001850 if (var.type().isEffectChild()) {
Brian Osman47726a12020-12-17 16:02:08 -05001851 childSlots++;
1852 } else if (is_uniform(var)) {
John Stiles47b087e2021-04-06 13:19:35 -04001853 uniformSlots += var.type().slotCount();
Brian Osman47726a12020-12-17 16:02:08 -05001854 }
1855 }
1856 }
Brian Osman0a442b72020-12-02 11:12:51 -05001857
Mike Kleinae562bd2021-01-08 14:15:55 -06001858 skvm::Uniforms uniforms(builder->uniform(), 0);
Brian Osman47726a12020-12-17 16:02:08 -05001859
1860 auto new_uni = [&]() { return builder->uniformF(uniforms.pushF(0.0f)); };
1861
1862 // Assume identity CTM
1863 skvm::Coord device = {pun_to_F32(builder->index()), new_uni()};
1864 skvm::Coord local = device;
1865
1866 struct Child {
1867 skvm::Uniform addr;
1868 skvm::I32 rowBytesAsPixels;
1869 };
1870
1871 std::vector<Child> children;
1872 for (int i = 0; i < childSlots; ++i) {
1873 children.push_back({uniforms.pushPtr(nullptr), builder->uniform32(uniforms.push(0))});
1874 }
1875
John Stilesd9a56b92021-07-23 15:50:39 -04001876 auto sampleShader = [&](int i, skvm::Coord coord) {
Mike Klein447f3312021-02-08 09:46:59 -06001877 skvm::PixelFormat pixelFormat = skvm::SkColorType_to_PixelFormat(kRGBA_F32_SkColorType);
Brian Osman3f904db2021-01-28 13:24:31 -05001878 skvm::I32 index = trunc(coord.x);
1879 index += trunc(coord.y) * children[i].rowBytesAsPixels;
Brian Osman47726a12020-12-17 16:02:08 -05001880 return gather(pixelFormat, children[i].addr, index);
1881 };
1882
1883 std::vector<skvm::Val> uniformVals;
1884 for (size_t i = 0; i < uniformSlots; ++i) {
1885 uniformVals.push_back(new_uni().id);
1886 }
1887
Brian Osman577c6062021-04-12 17:17:19 -04001888 skvm::Color inColor = builder->uniformColor(SkColors::kWhite, &uniforms);
John Stiles50d0d092021-06-09 17:24:31 -04001889 skvm::Color destColor = builder->uniformColor(SkColors::kBlack, &uniforms);
Brian Osman577c6062021-04-12 17:17:19 -04001890
John Stiles50d0d092021-06-09 17:24:31 -04001891 skvm::Color result = SkSL::ProgramToSkVM(program, *main, builder, SkMakeSpan(uniformVals),
John Stiles137482f2021-07-23 10:38:57 -04001892 device, local, inColor, destColor, sampleShader,
John Stiles2955c262021-07-23 15:51:05 -04001893 /*sampleColorFilter=*/nullptr,
1894 /*sampleBlender=*/nullptr);
Brian Osman47726a12020-12-17 16:02:08 -05001895
1896 storeF(builder->varying<float>(), result.r);
1897 storeF(builder->varying<float>(), result.g);
1898 storeF(builder->varying<float>(), result.b);
1899 storeF(builder->varying<float>(), result.a);
1900
1901 return true;
1902
1903}
1904
1905} // namespace SkSL