blob: 7a772d9eac7ea89abb95cfbb016671a924e0d7c3 [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"
18#include "src/sksl/ir/SkSLBoolLiteral.h"
19#include "src/sksl/ir/SkSLBreakStatement.h"
20#include "src/sksl/ir/SkSLConstructor.h"
John Stiles7384b372021-04-01 13:48:15 -040021#include "src/sksl/ir/SkSLConstructorArray.h"
John Stilese1182782021-03-30 22:09:37 -040022#include "src/sksl/ir/SkSLConstructorDiagonalMatrix.h"
John Stiles5abb9e12021-04-06 13:47:19 -040023#include "src/sksl/ir/SkSLConstructorMatrixResize.h"
John Stiles2938eea2021-04-01 18:58:25 -040024#include "src/sksl/ir/SkSLConstructorSplat.h"
John Stilesd47330f2021-04-08 23:25:52 -040025#include "src/sksl/ir/SkSLConstructorStruct.h"
Brian Osman0a442b72020-12-02 11:12:51 -050026#include "src/sksl/ir/SkSLContinueStatement.h"
27#include "src/sksl/ir/SkSLDoStatement.h"
28#include "src/sksl/ir/SkSLExpressionStatement.h"
29#include "src/sksl/ir/SkSLExternalFunctionCall.h"
Brian Osmanbe0b3b72021-01-06 14:27:35 -050030#include "src/sksl/ir/SkSLExternalFunctionReference.h"
Brian Osman0a442b72020-12-02 11:12:51 -050031#include "src/sksl/ir/SkSLFieldAccess.h"
32#include "src/sksl/ir/SkSLFloatLiteral.h"
33#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"
39#include "src/sksl/ir/SkSLIntLiteral.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 Osman54515b72021-01-07 14:38:08 -0500104 SkSpan<skvm::Val> asSpan() { return fVals; }
105
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,
116 SkSpan<skvm::Val> uniforms,
Brian Osman0a442b72020-12-02 11:12:51 -0500117 skvm::Coord device,
118 skvm::Coord local,
Brian Osmandb2dad52021-01-07 14:08:30 -0500119 SampleChildFn sampleChild);
Brian Osman0a442b72020-12-02 11:12:51 -0500120
Brian Osmandb2dad52021-01-07 14:08:30 -0500121 void writeFunction(const FunctionDefinition& function,
122 SkSpan<skvm::Val> arguments,
123 SkSpan<skvm::Val> outReturn);
Brian Osman0a442b72020-12-02 11:12:51 -0500124
125private:
126 enum class Intrinsic {
127 // sksl_public.sksl declares these intrinsics (and defines some other inline)
128
129 // Angle & Trigonometry
Brian Osman22cc3be2020-12-30 10:38:15 -0500130 kRadians,
131 kDegrees,
Brian Osman0a442b72020-12-02 11:12:51 -0500132 kSin,
133 kCos,
134 kTan,
135
136 kASin,
137 kACos,
138 kATan,
139
140 // Exponential
141 kPow,
142 kExp,
143 kLog,
144 kExp2,
145 kLog2,
146
147 kSqrt,
148 kInverseSqrt,
149
150 // Common
151 kAbs,
152 kSign,
153 kFloor,
154 kCeil,
155 kFract,
156 kMod,
157
158 kMin,
159 kMax,
160 kClamp,
161 kSaturate,
162 kMix,
163 kStep,
164 kSmoothstep,
165
166 // Geometric
167 kLength,
168 kDistance,
169 kDot,
Brian Osman22cc3be2020-12-30 10:38:15 -0500170 kCross,
Brian Osman0a442b72020-12-02 11:12:51 -0500171 kNormalize,
Brian Osman22cc3be2020-12-30 10:38:15 -0500172 kFaceforward,
173 kReflect,
174 kRefract,
Brian Osman0a442b72020-12-02 11:12:51 -0500175
176 // Matrix
Brian Osman93aed9a2020-12-28 15:18:46 -0500177 kMatrixCompMult,
Brian Osman0a442b72020-12-02 11:12:51 -0500178 kInverse,
179
180 // Vector Relational
181 kLessThan,
182 kLessThanEqual,
183 kGreaterThan,
184 kGreaterThanEqual,
185 kEqual,
186 kNotEqual,
187
188 kAny,
189 kAll,
190 kNot,
191
192 // SkSL
193 kSample,
194 };
195
Brian Osman0a442b72020-12-02 11:12:51 -0500196 /**
197 * In SkSL, a Variable represents a named, typed value (along with qualifiers, etc).
Brian Osman21f57072021-01-25 13:51:57 -0500198 * Every Variable is mapped to one (or several, contiguous) indices into our vector of
Brian Osman0a442b72020-12-02 11:12:51 -0500199 * skvm::Val. Those skvm::Val entries hold the current actual value of that variable.
200 *
201 * NOTE: Conceptually, each Variable is just mapped to a Value. We could implement it that way,
Brian Osman21f57072021-01-25 13:51:57 -0500202 * (and eliminate the indirection), but it would add overhead for each Variable,
Brian Osman0a442b72020-12-02 11:12:51 -0500203 * and add additional (different) bookkeeping for things like lvalue-swizzles.
204 *
205 * Any time a variable appears in an expression, that's a VariableReference, which is a kind of
206 * Expression. Evaluating that VariableReference (or any other Expression) produces a Value,
207 * which is a set of skvm::Val. (This allows an Expression to produce a vector or matrix, in
208 * addition to a scalar).
209 *
Brian Osman21f57072021-01-25 13:51:57 -0500210 * For a VariableReference, producing a Value is straightforward - we get the slot of the
211 * Variable (from fVariableMap), use that to look up the current skvm::Vals holding the
212 * variable's contents, and construct a Value with those ids.
Brian Osman0a442b72020-12-02 11:12:51 -0500213 */
214
215 /**
Brian Osman21f57072021-01-25 13:51:57 -0500216 * Returns the slot holding v's Val(s). Allocates storage if this is first time 'v' is
Brian Osman0a442b72020-12-02 11:12:51 -0500217 * referenced. Compound variables (e.g. vectors) will consume more than one slot, with
218 * getSlot returning the start of the contiguous chunk of slots.
219 */
Brian Osman21f57072021-01-25 13:51:57 -0500220 size_t getSlot(const Variable& v);
Brian Osman0a442b72020-12-02 11:12:51 -0500221
Mike Kleinaebcf732021-01-14 10:15:00 -0600222 skvm::F32 f32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
223 skvm::I32 i32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
Brian Osman0a442b72020-12-02 11:12:51 -0500224
225 // Shorthand for scalars
226 skvm::F32 f32(const Value& v) { SkASSERT(v.slots() == 1); return f32(v[0]); }
227 skvm::I32 i32(const Value& v) { SkASSERT(v.slots() == 1); return i32(v[0]); }
228
229 template <typename Fn>
230 Value unary(const Value& v, Fn&& fn) {
231 Value result(v.slots());
232 for (size_t i = 0; i < v.slots(); ++i) {
233 result[i] = fn({fBuilder, v[i]});
234 }
235 return result;
236 }
237
Brian Osman54515b72021-01-07 14:38:08 -0500238 skvm::I32 mask() {
239 // As we encounter (possibly conditional) return statements, fReturned is updated to store
240 // the lanes that have already returned. For the remainder of the current function, those
241 // lanes should be disabled.
Brian Osman9333c872021-01-13 15:06:17 -0500242 return fConditionMask & fLoopMask & ~currentFunction().fReturned;
Brian Osman54515b72021-01-07 14:38:08 -0500243 }
Brian Osman0a442b72020-12-02 11:12:51 -0500244
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500245 size_t fieldSlotOffset(const FieldAccess& expr);
246 size_t indexSlotOffset(const IndexExpression& expr);
247
Brian Osman0a442b72020-12-02 11:12:51 -0500248 Value writeExpression(const Expression& expr);
249 Value writeBinaryExpression(const BinaryExpression& b);
John Stilesd986f472021-04-06 15:54:43 -0400250 Value writeAggregationConstructor(const AnyConstructor& c);
John Stilese1182782021-03-30 22:09:37 -0400251 Value writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& c);
John Stiles5abb9e12021-04-06 13:47:19 -0400252 Value writeConstructorMatrixResize(const ConstructorMatrixResize& c);
John Stilesb14a8192021-04-05 11:40:46 -0400253 Value writeConstructorCast(const AnyConstructor& c);
John Stiles2938eea2021-04-01 18:58:25 -0400254 Value writeConstructorSplat(const ConstructorSplat& c);
Brian Osman0a442b72020-12-02 11:12:51 -0500255 Value writeFunctionCall(const FunctionCall& c);
Brian Osmandd50b0c2021-01-11 17:04:29 -0500256 Value writeExternalFunctionCall(const ExternalFunctionCall& c);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500257 Value writeFieldAccess(const FieldAccess& expr);
258 Value writeIndexExpression(const IndexExpression& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500259 Value writeIntrinsicCall(const FunctionCall& c);
260 Value writePostfixExpression(const PostfixExpression& p);
261 Value writePrefixExpression(const PrefixExpression& p);
262 Value writeSwizzle(const Swizzle& swizzle);
263 Value writeTernaryExpression(const TernaryExpression& t);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500264 Value writeVariableExpression(const VariableReference& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500265
John Stilesfd7252f2021-04-04 22:24:40 -0400266 Value writeTypeConversion(const Value& src, Type::NumberKind srcKind, Type::NumberKind dstKind);
267
Brian Osman0a442b72020-12-02 11:12:51 -0500268 void writeStatement(const Statement& s);
269 void writeBlock(const Block& b);
Brian Osman9333c872021-01-13 15:06:17 -0500270 void writeBreakStatement();
271 void writeContinueStatement();
272 void writeForStatement(const ForStatement& f);
Brian Osman0a442b72020-12-02 11:12:51 -0500273 void writeIfStatement(const IfStatement& stmt);
274 void writeReturnStatement(const ReturnStatement& r);
275 void writeVarDeclaration(const VarDeclaration& decl);
276
277 Value writeStore(const Expression& lhs, const Value& rhs);
278
279 Value writeMatrixInverse2x2(const Value& m);
280 Value writeMatrixInverse3x3(const Value& m);
281 Value writeMatrixInverse4x4(const Value& m);
282
Brian Osmandb2dad52021-01-07 14:08:30 -0500283 //
284 // Global state for the lifetime of the generator:
285 //
Brian Osman0a442b72020-12-02 11:12:51 -0500286 const Program& fProgram;
Brian Osman0a442b72020-12-02 11:12:51 -0500287 skvm::Builder* fBuilder;
288
Brian Osman0a442b72020-12-02 11:12:51 -0500289 const skvm::Coord fLocalCoord;
290 const SampleChildFn fSampleChild;
Brian Osman0a442b72020-12-02 11:12:51 -0500291
292 // [Variable, first slot in fSlots]
Brian Osman21f57072021-01-25 13:51:57 -0500293 std::unordered_map<const Variable*, size_t> fVariableMap;
Brian Osmandb2dad52021-01-07 14:08:30 -0500294 std::vector<skvm::Val> fSlots;
Brian Osman0a442b72020-12-02 11:12:51 -0500295
Brian Osman9333c872021-01-13 15:06:17 -0500296 // Conditional execution mask (managed by ScopedCondition, and tied to control-flow scopes)
297 skvm::I32 fConditionMask;
298
299 // Similar: loop execution masks. Each loop starts with all lanes active (fLoopMask).
300 // 'break' disables a lane in fLoopMask until the loop finishes
301 // 'continue' disables a lane in fLoopMask, and sets fContinueMask to be re-enabled on the next
302 // iteration
303 skvm::I32 fLoopMask;
304 skvm::I32 fContinueMask;
Brian Osman54515b72021-01-07 14:38:08 -0500305
Brian Osmandb2dad52021-01-07 14:08:30 -0500306 //
307 // State that's local to the generation of a single function:
308 //
Brian Osman54515b72021-01-07 14:38:08 -0500309 struct Function {
310 const SkSpan<skvm::Val> fReturnValue;
311 skvm::I32 fReturned;
312 };
313 std::vector<Function> fFunctionStack;
314 Function& currentFunction() { return fFunctionStack.back(); }
Brian Osman0a442b72020-12-02 11:12:51 -0500315
Brian Osman9333c872021-01-13 15:06:17 -0500316 class ScopedCondition {
Brian Osman0a442b72020-12-02 11:12:51 -0500317 public:
Brian Osman9333c872021-01-13 15:06:17 -0500318 ScopedCondition(SkVMGenerator* generator, skvm::I32 mask)
319 : fGenerator(generator), fOldConditionMask(fGenerator->fConditionMask) {
320 fGenerator->fConditionMask &= mask;
Brian Osman0a442b72020-12-02 11:12:51 -0500321 }
322
Brian Osman9333c872021-01-13 15:06:17 -0500323 ~ScopedCondition() { fGenerator->fConditionMask = fOldConditionMask; }
Brian Osman0a442b72020-12-02 11:12:51 -0500324
325 private:
326 SkVMGenerator* fGenerator;
Brian Osman9333c872021-01-13 15:06:17 -0500327 skvm::I32 fOldConditionMask;
Brian Osman0a442b72020-12-02 11:12:51 -0500328 };
329};
330
331static Type::NumberKind base_number_kind(const Type& type) {
332 if (type.typeKind() == Type::TypeKind::kMatrix || type.typeKind() == Type::TypeKind::kVector) {
333 return base_number_kind(type.componentType());
334 }
335 return type.numberKind();
336}
337
338static inline bool is_uniform(const SkSL::Variable& var) {
339 return var.modifiers().fFlags & Modifiers::kUniform_Flag;
340}
341
Brian Osman0a442b72020-12-02 11:12:51 -0500342SkVMGenerator::SkVMGenerator(const Program& program,
Brian Osman0a442b72020-12-02 11:12:51 -0500343 skvm::Builder* builder,
344 SkSpan<skvm::Val> uniforms,
Brian Osman0a442b72020-12-02 11:12:51 -0500345 skvm::Coord device,
346 skvm::Coord local,
Brian Osmandb2dad52021-01-07 14:08:30 -0500347 SampleChildFn sampleChild)
Brian Osman0a442b72020-12-02 11:12:51 -0500348 : fProgram(program)
Brian Osman0a442b72020-12-02 11:12:51 -0500349 , fBuilder(builder)
350 , fLocalCoord(local)
Brian Osman317e5882021-03-11 11:11:45 -0500351 , fSampleChild(std::move(sampleChild)) {
Brian Osman9333c872021-01-13 15:06:17 -0500352 fConditionMask = fLoopMask = fBuilder->splat(0xffff'ffff);
Brian Osman0a442b72020-12-02 11:12:51 -0500353
354 // Now, add storage for each global variable (including uniforms) to fSlots, and entries in
355 // fVariableMap to remember where every variable is stored.
356 const skvm::Val* uniformIter = uniforms.begin();
357 size_t fpCount = 0;
358 for (const ProgramElement* e : fProgram.elements()) {
359 if (e->is<GlobalVarDeclaration>()) {
Brian Osmanc0576692021-02-17 13:52:35 -0500360 const GlobalVarDeclaration& gvd = e->as<GlobalVarDeclaration>();
361 const VarDeclaration& decl = gvd.declaration()->as<VarDeclaration>();
362 const Variable& var = decl.var();
Brian Osman0a442b72020-12-02 11:12:51 -0500363 SkASSERT(fVariableMap.find(&var) == fVariableMap.end());
364
Brian Osman14d00962021-04-02 17:04:35 -0400365 // For most variables, fVariableMap stores an index into fSlots, but for children,
366 // fVariableMap stores the index to pass to fSampleChild().
367 if (var.type().isEffectChild()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500368 fVariableMap[&var] = fpCount++;
369 continue;
370 }
371
372 // Opaque types include fragment processors, GL objects (samplers, textures, etc), and
373 // special types like 'void'. Of those, only fragment processors are legal variables.
374 SkASSERT(!var.type().isOpaque());
375
Brian Osmanc0576692021-02-17 13:52:35 -0500376 // getSlot() allocates space for the variable's value in fSlots, initializes it to zero,
377 // and populates fVariableMap.
378 size_t slot = this->getSlot(var),
John Stiles47b087e2021-04-06 13:19:35 -0400379 nslots = var.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500380
381 if (int builtin = var.modifiers().fLayout.fBuiltin; builtin >= 0) {
382 // builtin variables are system-defined, with special semantics. The only builtin
383 // variable exposed to runtime effects is sk_FragCoord.
384 switch (builtin) {
385 case SK_FRAGCOORD_BUILTIN:
386 SkASSERT(nslots == 4);
Brian Osmanc0576692021-02-17 13:52:35 -0500387 fSlots[slot + 0] = device.x.id;
388 fSlots[slot + 1] = device.y.id;
389 fSlots[slot + 2] = fBuilder->splat(0.0f).id;
390 fSlots[slot + 3] = fBuilder->splat(1.0f).id;
Brian Osman0a442b72020-12-02 11:12:51 -0500391 break;
392 default:
393 SkDEBUGFAIL("Unsupported builtin");
394 }
395 } else if (is_uniform(var)) {
396 // For uniforms, copy the supplied IDs over
397 SkASSERT(uniformIter + nslots <= uniforms.end());
Brian Osmanc0576692021-02-17 13:52:35 -0500398 std::copy(uniformIter, uniformIter + nslots, fSlots.begin() + slot);
Brian Osman0a442b72020-12-02 11:12:51 -0500399 uniformIter += nslots;
Brian Osmanc0576692021-02-17 13:52:35 -0500400 } else if (decl.value()) {
401 // For other globals, populate with the initializer expression (if there is one)
402 Value val = this->writeExpression(*decl.value());
403 for (size_t i = 0; i < nslots; ++i) {
404 fSlots[slot + i] = val[i];
405 }
Brian Osman0a442b72020-12-02 11:12:51 -0500406 }
407 }
408 }
409 SkASSERT(uniformIter == uniforms.end());
Brian Osman0a442b72020-12-02 11:12:51 -0500410}
411
Brian Osmandb2dad52021-01-07 14:08:30 -0500412void SkVMGenerator::writeFunction(const FunctionDefinition& function,
413 SkSpan<skvm::Val> arguments,
414 SkSpan<skvm::Val> outReturn) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500415 const FunctionDeclaration& decl = function.declaration();
John Stiles47b087e2021-04-06 13:19:35 -0400416 SkASSERT(decl.returnType().slotCount() == outReturn.size());
Brian Osmandb2dad52021-01-07 14:08:30 -0500417
Brian Osman54515b72021-01-07 14:38:08 -0500418 fFunctionStack.push_back({outReturn, /*returned=*/fBuilder->splat(0)});
Brian Osmandb2dad52021-01-07 14:08:30 -0500419
420 // For all parameters, copy incoming argument IDs to our vector of (all) variable IDs
Brian Osman5933d4c2021-01-05 13:02:20 -0500421 size_t argIdx = 0;
Brian Osmandb2dad52021-01-07 14:08:30 -0500422 for (const Variable* p : decl.parameters()) {
Brian Osman21f57072021-01-25 13:51:57 -0500423 size_t paramSlot = this->getSlot(*p),
John Stiles47b087e2021-04-06 13:19:35 -0400424 nslots = p->type().slotCount();
Brian Osman5933d4c2021-01-05 13:02:20 -0500425
Brian Osmandb2dad52021-01-07 14:08:30 -0500426 for (size_t i = 0; i < nslots; ++i) {
427 fSlots[paramSlot + i] = arguments[argIdx + i];
428 }
429 argIdx += nslots;
430 }
431 SkASSERT(argIdx == arguments.size());
432
433 this->writeStatement(*function.body());
434
435 // Copy 'out' and 'inout' parameters back to their caller-supplied argument storage
436 argIdx = 0;
437 for (const Variable* p : decl.parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -0400438 size_t nslots = p->type().slotCount();
Brian Osmandb2dad52021-01-07 14:08:30 -0500439
Brian Osman5933d4c2021-01-05 13:02:20 -0500440 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
Brian Osman21f57072021-01-25 13:51:57 -0500441 size_t paramSlot = this->getSlot(*p);
Brian Osman5933d4c2021-01-05 13:02:20 -0500442 for (size_t i = 0; i < nslots; ++i) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500443 arguments[argIdx + i] = fSlots[paramSlot + i];
Brian Osman5933d4c2021-01-05 13:02:20 -0500444 }
445 }
446 argIdx += nslots;
447 }
Brian Osmandb2dad52021-01-07 14:08:30 -0500448 SkASSERT(argIdx == arguments.size());
Brian Osman54515b72021-01-07 14:38:08 -0500449
450 fFunctionStack.pop_back();
Brian Osman0a442b72020-12-02 11:12:51 -0500451}
452
Brian Osman21f57072021-01-25 13:51:57 -0500453size_t SkVMGenerator::getSlot(const Variable& v) {
Brian Osman0a442b72020-12-02 11:12:51 -0500454 auto entry = fVariableMap.find(&v);
455 if (entry != fVariableMap.end()) {
456 return entry->second;
457 }
458
Brian Osman0a442b72020-12-02 11:12:51 -0500459 size_t slot = fSlots.size(),
John Stiles47b087e2021-04-06 13:19:35 -0400460 nslots = v.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500461 fSlots.resize(slot + nslots, fBuilder->splat(0.0f).id);
462 fVariableMap[&v] = slot;
463 return slot;
464}
465
Brian Osman0a442b72020-12-02 11:12:51 -0500466Value SkVMGenerator::writeBinaryExpression(const BinaryExpression& b) {
467 const Expression& left = *b.left();
468 const Expression& right = *b.right();
John Stiles45990502021-02-16 10:55:27 -0500469 Operator op = b.getOperator();
470 if (op.kind() == Token::Kind::TK_EQ) {
Brian Osman0a442b72020-12-02 11:12:51 -0500471 return this->writeStore(left, this->writeExpression(right));
472 }
473
474 const Type& lType = left.type();
475 const Type& rType = right.type();
476 bool lVecOrMtx = (lType.isVector() || lType.isMatrix());
477 bool rVecOrMtx = (rType.isVector() || rType.isMatrix());
John Stiles45990502021-02-16 10:55:27 -0500478 bool isAssignment = op.isAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500479 if (isAssignment) {
John Stiles45990502021-02-16 10:55:27 -0500480 op = op.removeAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500481 }
482 Type::NumberKind nk = base_number_kind(lType);
483
484 // A few ops require special treatment:
John Stiles45990502021-02-16 10:55:27 -0500485 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500486 case Token::Kind::TK_LOGICALAND: {
487 SkASSERT(!isAssignment);
488 SkASSERT(nk == Type::NumberKind::kBoolean);
489 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500490 ScopedCondition shortCircuit(this, lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500491 skvm::I32 rVal = i32(this->writeExpression(right));
492 return lVal & rVal;
493 }
494 case Token::Kind::TK_LOGICALOR: {
495 SkASSERT(!isAssignment);
496 SkASSERT(nk == Type::NumberKind::kBoolean);
497 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500498 ScopedCondition shortCircuit(this, ~lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500499 skvm::I32 rVal = i32(this->writeExpression(right));
500 return lVal | rVal;
501 }
John Stiles94e72b92021-01-30 11:06:18 -0500502 case Token::Kind::TK_COMMA:
503 // We write the left side of the expression to preserve its side effects, even though we
504 // immediately discard the result.
505 this->writeExpression(left);
506 return this->writeExpression(right);
Brian Osman0a442b72020-12-02 11:12:51 -0500507 default:
508 break;
509 }
510
511 // All of the other ops always evaluate both sides of the expression
512 Value lVal = this->writeExpression(left),
513 rVal = this->writeExpression(right);
514
515 // Special case for M*V, V*M, M*M (but not V*V!)
John Stiles45990502021-02-16 10:55:27 -0500516 if (op.kind() == Token::Kind::TK_STAR
Brian Osman0a442b72020-12-02 11:12:51 -0500517 && lVecOrMtx && rVecOrMtx && !(lType.isVector() && rType.isVector())) {
518 int rCols = rType.columns(),
519 rRows = rType.rows(),
520 lCols = lType.columns(),
521 lRows = lType.rows();
522 // M*V treats the vector as a column
523 if (rType.isVector()) {
524 std::swap(rCols, rRows);
525 }
526 SkASSERT(lCols == rRows);
John Stiles47b087e2021-04-06 13:19:35 -0400527 SkASSERT(b.type().slotCount() == static_cast<size_t>(lRows * rCols));
Brian Osman0a442b72020-12-02 11:12:51 -0500528 Value result(lRows * rCols);
529 size_t resultIdx = 0;
530 for (int c = 0; c < rCols; ++c)
531 for (int r = 0; r < lRows; ++r) {
532 skvm::F32 sum = fBuilder->splat(0.0f);
533 for (int j = 0; j < lCols; ++j) {
534 sum += f32(lVal[j*lRows + r]) * f32(rVal[c*rRows + j]);
535 }
536 result[resultIdx++] = sum;
537 }
538 SkASSERT(resultIdx == result.slots());
539 return isAssignment ? this->writeStore(left, result) : result;
540 }
541
542 size_t nslots = std::max(lVal.slots(), rVal.slots());
543
Brian Osman0a442b72020-12-02 11:12:51 -0500544 auto binary = [&](auto&& f_fn, auto&& i_fn) {
545 Value result(nslots);
546 for (size_t i = 0; i < nslots; ++i) {
547 // If one side is scalar, replicate it to all channels
548 skvm::Val L = lVal.slots() == 1 ? lVal[0] : lVal[i],
549 R = rVal.slots() == 1 ? rVal[0] : rVal[i];
550 if (nk == Type::NumberKind::kFloat) {
551 result[i] = f_fn(f32(L), f32(R));
552 } else {
553 result[i] = i_fn(i32(L), i32(R));
554 }
555 }
556 return isAssignment ? this->writeStore(left, result) : result;
557 };
558
559 auto unsupported_f = [&](skvm::F32, skvm::F32) {
560 SkDEBUGFAIL("Unsupported operator");
561 return skvm::F32{};
562 };
563
John Stiles45990502021-02-16 10:55:27 -0500564 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500565 case Token::Kind::TK_EQEQ: {
566 SkASSERT(!isAssignment);
567 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x == y; },
568 [](skvm::I32 x, skvm::I32 y) { return x == y; });
569 skvm::I32 folded = i32(cmp[0]);
570 for (size_t i = 1; i < nslots; ++i) {
571 folded &= i32(cmp[i]);
572 }
573 return folded;
574 }
575 case Token::Kind::TK_NEQ: {
576 SkASSERT(!isAssignment);
577 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x != y; },
578 [](skvm::I32 x, skvm::I32 y) { return x != y; });
579 skvm::I32 folded = i32(cmp[0]);
580 for (size_t i = 1; i < nslots; ++i) {
581 folded |= i32(cmp[i]);
582 }
583 return folded;
584 }
585 case Token::Kind::TK_GT:
586 return binary([](skvm::F32 x, skvm::F32 y) { return x > y; },
587 [](skvm::I32 x, skvm::I32 y) { return x > y; });
588 case Token::Kind::TK_GTEQ:
589 return binary([](skvm::F32 x, skvm::F32 y) { return x >= y; },
590 [](skvm::I32 x, skvm::I32 y) { return x >= y; });
591 case Token::Kind::TK_LT:
592 return binary([](skvm::F32 x, skvm::F32 y) { return x < y; },
593 [](skvm::I32 x, skvm::I32 y) { return x < y; });
594 case Token::Kind::TK_LTEQ:
595 return binary([](skvm::F32 x, skvm::F32 y) { return x <= y; },
596 [](skvm::I32 x, skvm::I32 y) { return x <= y; });
597
598 case Token::Kind::TK_PLUS:
599 return binary([](skvm::F32 x, skvm::F32 y) { return x + y; },
600 [](skvm::I32 x, skvm::I32 y) { return x + y; });
601 case Token::Kind::TK_MINUS:
602 return binary([](skvm::F32 x, skvm::F32 y) { return x - y; },
603 [](skvm::I32 x, skvm::I32 y) { return x - y; });
604 case Token::Kind::TK_STAR:
Mike Kleinff4decc2021-02-10 16:13:35 -0600605 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; },
Brian Osman0a442b72020-12-02 11:12:51 -0500606 [](skvm::I32 x, skvm::I32 y) { return x * y; });
607 case Token::Kind::TK_SLASH:
608 // Minimum spec (GLSL ES 1.0) has very loose requirements for integer operations.
609 // (Low-end GPUs may not have integer ALUs). Given that, we are allowed to do floating
610 // point division plus rounding. Section 10.28 of the spec even clarifies that the
611 // rounding mode is undefined (but round-towards-zero is the obvious/common choice).
612 return binary([](skvm::F32 x, skvm::F32 y) { return x / y; },
613 [](skvm::I32 x, skvm::I32 y) {
614 return skvm::trunc(skvm::to_F32(x) / skvm::to_F32(y));
615 });
616
617 case Token::Kind::TK_BITWISEXOR:
618 case Token::Kind::TK_LOGICALXOR:
619 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x ^ y; });
620 case Token::Kind::TK_BITWISEAND:
621 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x & y; });
622 case Token::Kind::TK_BITWISEOR:
623 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x | y; });
624
625 // These three operators are all 'reserved' (illegal) in our minimum spec, but will require
626 // implementation in the future.
627 case Token::Kind::TK_PERCENT:
628 case Token::Kind::TK_SHL:
629 case Token::Kind::TK_SHR:
630 default:
631 SkDEBUGFAIL("Unsupported operator");
632 return {};
633 }
634}
635
John Stilesd986f472021-04-06 15:54:43 -0400636Value SkVMGenerator::writeAggregationConstructor(const AnyConstructor& c) {
John Stiles47b087e2021-04-06 13:19:35 -0400637 Value result(c.type().slotCount());
John Stiles626b62e2021-03-31 22:06:07 -0400638 size_t resultIdx = 0;
John Stilesd986f472021-04-06 15:54:43 -0400639 for (const auto &arg : c.argumentSpan()) {
John Stiles626b62e2021-03-31 22:06:07 -0400640 Value tmp = this->writeExpression(*arg);
641 for (size_t tmpSlot = 0; tmpSlot < tmp.slots(); ++tmpSlot) {
642 result[resultIdx++] = tmp[tmpSlot];
643 }
644 }
645 return result;
646}
647
John Stilesfd7252f2021-04-04 22:24:40 -0400648Value SkVMGenerator::writeTypeConversion(const Value& src,
649 Type::NumberKind srcKind,
650 Type::NumberKind dstKind) {
651 // Conversion among "similar" types (floatN <-> halfN), (shortN <-> intN), etc. is a no-op.
652 if (srcKind == dstKind) {
653 return src;
654 }
655
656 // TODO: Handle signed vs. unsigned. GLSL ES 1.0 only has 'int', so no problem yet.
657 Value dst(src.slots());
658 switch (dstKind) {
659 case Type::NumberKind::kFloat:
660 if (srcKind == Type::NumberKind::kSigned) {
661 // int -> float
662 for (size_t i = 0; i < src.slots(); ++i) {
663 dst[i] = skvm::to_F32(i32(src[i]));
664 }
665 return dst;
666 }
667 if (srcKind == Type::NumberKind::kBoolean) {
668 // bool -> float
669 for (size_t i = 0; i < src.slots(); ++i) {
670 dst[i] = skvm::select(i32(src[i]), 1.0f, 0.0f);
671 }
672 return dst;
673 }
674 break;
675
676 case Type::NumberKind::kSigned:
677 if (srcKind == Type::NumberKind::kFloat) {
678 // float -> int
679 for (size_t i = 0; i < src.slots(); ++i) {
680 dst[i] = skvm::trunc(f32(src[i]));
681 }
682 return dst;
683 }
684 if (srcKind == Type::NumberKind::kBoolean) {
685 // bool -> int
686 for (size_t i = 0; i < src.slots(); ++i) {
687 dst[i] = skvm::select(i32(src[i]), 1, 0);
688 }
689 return dst;
690 }
691 break;
692
693 case Type::NumberKind::kBoolean:
694 if (srcKind == Type::NumberKind::kSigned) {
695 // int -> bool
696 for (size_t i = 0; i < src.slots(); ++i) {
697 dst[i] = i32(src[i]) != 0;
698 }
699 return dst;
700 }
701 if (srcKind == Type::NumberKind::kFloat) {
702 // float -> bool
703 for (size_t i = 0; i < src.slots(); ++i) {
704 dst[i] = f32(src[i]) != 0.0;
705 }
706 return dst;
707 }
708 break;
709
710 default:
711 break;
712 }
713 SkDEBUGFAILF("Unsupported type conversion: %d -> %d", srcKind, dstKind);
714 return {};
715}
716
John Stilesb14a8192021-04-05 11:40:46 -0400717Value SkVMGenerator::writeConstructorCast(const AnyConstructor& c) {
718 auto arguments = c.argumentSpan();
719 SkASSERT(arguments.size() == 1);
720 const Expression& argument = *arguments.front();
721
722 const Type& srcType = argument.type();
John Stilesfd7252f2021-04-04 22:24:40 -0400723 const Type& dstType = c.type();
724 Type::NumberKind srcKind = base_number_kind(srcType);
725 Type::NumberKind dstKind = base_number_kind(dstType);
John Stilesb14a8192021-04-05 11:40:46 -0400726 Value src = this->writeExpression(argument);
John Stilesfd7252f2021-04-04 22:24:40 -0400727 return this->writeTypeConversion(src, srcKind, dstKind);
728}
729
John Stiles2938eea2021-04-01 18:58:25 -0400730Value SkVMGenerator::writeConstructorSplat(const ConstructorSplat& c) {
731 SkASSERT(c.type().isVector());
732 SkASSERT(c.argument()->type().isScalar());
733 int columns = c.type().columns();
734
735 // Splat the argument across all components of a vector.
736 Value src = this->writeExpression(*c.argument());
737 Value dst(columns);
738 for (int i = 0; i < columns; ++i) {
739 dst[i] = src[0];
740 }
741 return dst;
742}
743
John Stilese1182782021-03-30 22:09:37 -0400744Value SkVMGenerator::writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& c) {
745 const Type& dstType = c.type();
746 SkASSERT(dstType.isMatrix());
747 SkASSERT(c.argument()->type() == dstType.componentType());
748
749 Value src = this->writeExpression(*c.argument());
750 Value dst(dstType.rows() * dstType.columns());
751 size_t dstIndex = 0;
752
753 // Matrix-from-scalar builds a diagonal scale matrix
754 for (int c = 0; c < dstType.columns(); ++c) {
755 for (int r = 0; r < dstType.rows(); ++r) {
756 dst[dstIndex++] = (c == r ? f32(src) : fBuilder->splat(0.0f));
757 }
758 }
759
760 SkASSERT(dstIndex == dst.slots());
761 return dst;
762}
763
John Stiles5abb9e12021-04-06 13:47:19 -0400764Value SkVMGenerator::writeConstructorMatrixResize(const ConstructorMatrixResize& c) {
765 const Type& srcType = c.argument()->type();
766 const Type& dstType = c.type();
767 Value src = this->writeExpression(*c.argument());
768 Value dst(dstType.rows() * dstType.columns());
769
770 // Matrix-from-matrix uses src where it overlaps, and fills in missing fields with identity.
771 size_t dstIndex = 0;
772 for (int c = 0; c < dstType.columns(); ++c) {
773 for (int r = 0; r < dstType.rows(); ++r) {
774 if (c < srcType.columns() && r < srcType.rows()) {
775 dst[dstIndex++] = src[c * srcType.rows() + r];
776 } else {
777 dst[dstIndex++] = fBuilder->splat(c == r ? 1.0f : 0.0f);
778 }
779 }
780 }
781
782 SkASSERT(dstIndex == dst.slots());
783 return dst;
784}
785
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500786size_t SkVMGenerator::fieldSlotOffset(const FieldAccess& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500787 size_t offset = 0;
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500788 for (int i = 0; i < expr.fieldIndex(); ++i) {
John Stiles47b087e2021-04-06 13:19:35 -0400789 offset += (*expr.base()->type().fields()[i].fType).slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500790 }
791 return offset;
792}
793
794Value SkVMGenerator::writeFieldAccess(const FieldAccess& expr) {
795 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400796 Value field(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500797 size_t offset = this->fieldSlotOffset(expr);
798 for (size_t i = 0; i < field.slots(); ++i) {
799 field[i] = base[offset + i];
800 }
801 return field;
802}
803
804size_t SkVMGenerator::indexSlotOffset(const IndexExpression& expr) {
805 Value index = this->writeExpression(*expr.index());
806 int indexValue = -1;
807 SkAssertResult(fBuilder->allImm(index[0], &indexValue));
808
809 // When indexing by a literal, the front-end guarantees that we don't go out of bounds.
810 // But when indexing by a loop variable, it's possible to generate out-of-bounds access.
811 // The GLSL spec leaves that behavior undefined - we'll just clamp everything here.
812 indexValue = SkTPin(indexValue, 0, expr.base()->type().columns() - 1);
813
John Stiles47b087e2021-04-06 13:19:35 -0400814 size_t stride = expr.type().slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500815 return indexValue * stride;
816}
817
818Value SkVMGenerator::writeIndexExpression(const IndexExpression& expr) {
819 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400820 Value element(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500821 size_t offset = this->indexSlotOffset(expr);
822 for (size_t i = 0; i < element.slots(); ++i) {
823 element[i] = base[offset + i];
824 }
825 return element;
826}
827
828Value SkVMGenerator::writeVariableExpression(const VariableReference& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500829 size_t slot = this->getSlot(*expr.variable());
John Stiles47b087e2021-04-06 13:19:35 -0400830 Value val(expr.type().slotCount());
Brian Osman0a442b72020-12-02 11:12:51 -0500831 for (size_t i = 0; i < val.slots(); ++i) {
832 val[i] = fSlots[slot + i];
833 }
834 return val;
835}
836
837Value SkVMGenerator::writeMatrixInverse2x2(const Value& m) {
838 SkASSERT(m.slots() == 4);
839 skvm::F32 a = f32(m[0]),
840 b = f32(m[1]),
841 c = f32(m[2]),
842 d = f32(m[3]);
843 skvm::F32 idet = 1.0f / (a*d - b*c);
844
845 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600846 result[0] = ( d ** idet);
847 result[1] = (-b ** idet);
848 result[2] = (-c ** idet);
849 result[3] = ( a ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500850 return result;
851}
852
853Value SkVMGenerator::writeMatrixInverse3x3(const Value& m) {
854 SkASSERT(m.slots() == 9);
855 skvm::F32 a11 = f32(m[0]), a12 = f32(m[3]), a13 = f32(m[6]),
856 a21 = f32(m[1]), a22 = f32(m[4]), a23 = f32(m[7]),
857 a31 = f32(m[2]), a32 = f32(m[5]), a33 = f32(m[8]);
858 skvm::F32 idet = 1.0f / (a11*a22*a33 + a12*a23*a31 + a13*a21*a32 -
859 a11*a23*a32 - a12*a21*a33 - a13*a22*a31);
860
861 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600862 result[0] = ((a22**a33 - a23**a32) ** idet);
863 result[1] = ((a23**a31 - a21**a33) ** idet);
864 result[2] = ((a21**a32 - a22**a31) ** idet);
865 result[3] = ((a13**a32 - a12**a33) ** idet);
866 result[4] = ((a11**a33 - a13**a31) ** idet);
867 result[5] = ((a12**a31 - a11**a32) ** idet);
868 result[6] = ((a12**a23 - a13**a22) ** idet);
869 result[7] = ((a13**a21 - a11**a23) ** idet);
870 result[8] = ((a11**a22 - a12**a21) ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500871 return result;
872}
873
874Value SkVMGenerator::writeMatrixInverse4x4(const Value& m) {
875 SkASSERT(m.slots() == 16);
876 skvm::F32 a00 = f32(m[0]), a10 = f32(m[4]), a20 = f32(m[ 8]), a30 = f32(m[12]),
877 a01 = f32(m[1]), a11 = f32(m[5]), a21 = f32(m[ 9]), a31 = f32(m[13]),
878 a02 = f32(m[2]), a12 = f32(m[6]), a22 = f32(m[10]), a32 = f32(m[14]),
879 a03 = f32(m[3]), a13 = f32(m[7]), a23 = f32(m[11]), a33 = f32(m[15]);
880
Mike Kleinff4decc2021-02-10 16:13:35 -0600881 skvm::F32 b00 = a00**a11 - a01**a10,
882 b01 = a00**a12 - a02**a10,
883 b02 = a00**a13 - a03**a10,
884 b03 = a01**a12 - a02**a11,
885 b04 = a01**a13 - a03**a11,
886 b05 = a02**a13 - a03**a12,
887 b06 = a20**a31 - a21**a30,
888 b07 = a20**a32 - a22**a30,
889 b08 = a20**a33 - a23**a30,
890 b09 = a21**a32 - a22**a31,
891 b10 = a21**a33 - a23**a31,
892 b11 = a22**a33 - a23**a32;
Brian Osman0a442b72020-12-02 11:12:51 -0500893
Mike Kleinff4decc2021-02-10 16:13:35 -0600894 skvm::F32 idet = 1.0f / (b00**b11 - b01**b10 + b02**b09 + b03**b08 - b04**b07 + b05**b06);
Brian Osman0a442b72020-12-02 11:12:51 -0500895
896 b00 *= idet;
897 b01 *= idet;
898 b02 *= idet;
899 b03 *= idet;
900 b04 *= idet;
901 b05 *= idet;
902 b06 *= idet;
903 b07 *= idet;
904 b08 *= idet;
905 b09 *= idet;
906 b10 *= idet;
907 b11 *= idet;
908
909 Value result(m.slots());
910 result[ 0] = (a11*b11 - a12*b10 + a13*b09);
911 result[ 1] = (a02*b10 - a01*b11 - a03*b09);
912 result[ 2] = (a31*b05 - a32*b04 + a33*b03);
913 result[ 3] = (a22*b04 - a21*b05 - a23*b03);
914 result[ 4] = (a12*b08 - a10*b11 - a13*b07);
915 result[ 5] = (a00*b11 - a02*b08 + a03*b07);
916 result[ 6] = (a32*b02 - a30*b05 - a33*b01);
917 result[ 7] = (a20*b05 - a22*b02 + a23*b01);
918 result[ 8] = (a10*b10 - a11*b08 + a13*b06);
919 result[ 9] = (a01*b08 - a00*b10 - a03*b06);
920 result[10] = (a30*b04 - a31*b02 + a33*b00);
921 result[11] = (a21*b02 - a20*b04 - a23*b00);
922 result[12] = (a11*b07 - a10*b09 - a12*b06);
923 result[13] = (a00*b09 - a01*b07 + a02*b06);
924 result[14] = (a31*b01 - a30*b03 - a32*b00);
925 result[15] = (a20*b03 - a21*b01 + a22*b00);
926 return result;
927}
928
929Value SkVMGenerator::writeIntrinsicCall(const FunctionCall& c) {
Brian Osman317e5882021-03-11 11:11:45 -0500930 static std::unordered_map<String, Intrinsic> intrinsics {
931 { "radians", Intrinsic::kRadians },
932 { "degrees", Intrinsic::kDegrees },
933 { "sin", Intrinsic::kSin },
934 { "cos", Intrinsic::kCos },
935 { "tan", Intrinsic::kTan },
936 { "asin", Intrinsic::kASin },
937 { "acos", Intrinsic::kACos },
938 { "atan", Intrinsic::kATan },
939
940 { "pow", Intrinsic::kPow },
941 { "exp", Intrinsic::kExp },
942 { "log", Intrinsic::kLog },
943 { "exp2", Intrinsic::kExp2 },
944 { "log2", Intrinsic::kLog2 },
945 { "sqrt", Intrinsic::kSqrt },
946 { "inversesqrt", Intrinsic::kInverseSqrt },
947
948 { "abs", Intrinsic::kAbs },
949 { "sign", Intrinsic::kSign },
950 { "floor", Intrinsic::kFloor },
951 { "ceil", Intrinsic::kCeil },
952 { "fract", Intrinsic::kFract },
953 { "mod", Intrinsic::kMod },
954
955 { "min", Intrinsic::kMin },
956 { "max", Intrinsic::kMax },
957 { "clamp", Intrinsic::kClamp },
958 { "saturate", Intrinsic::kSaturate },
959 { "mix", Intrinsic::kMix },
960 { "step", Intrinsic::kStep },
961 { "smoothstep", Intrinsic::kSmoothstep },
962
963 { "length", Intrinsic::kLength },
964 { "distance", Intrinsic::kDistance },
965 { "dot", Intrinsic::kDot },
966 { "cross", Intrinsic::kCross },
967 { "normalize", Intrinsic::kNormalize },
968 { "faceforward", Intrinsic::kFaceforward },
969 { "reflect", Intrinsic::kReflect },
970 { "refract", Intrinsic::kRefract },
971
972 { "matrixCompMult", Intrinsic::kMatrixCompMult },
973 { "inverse", Intrinsic::kInverse },
974
975 { "lessThan", Intrinsic::kLessThan },
976 { "lessThanEqual", Intrinsic::kLessThanEqual },
977 { "greaterThan", Intrinsic::kGreaterThan },
978 { "greaterThanEqual", Intrinsic::kGreaterThanEqual },
979 { "equal", Intrinsic::kEqual },
980 { "notEqual", Intrinsic::kNotEqual },
981
982 { "any", Intrinsic::kAny },
983 { "all", Intrinsic::kAll },
984 { "not", Intrinsic::kNot },
985
986 { "sample", Intrinsic::kSample } };
987
988 auto found = intrinsics.find(c.function().name());
989 if (found == intrinsics.end()) {
Brian Osman47726a12020-12-17 16:02:08 -0500990 SkDEBUGFAILF("Missing intrinsic: '%s'", String(c.function().name()).c_str());
Brian Osman0a442b72020-12-02 11:12:51 -0500991 return {};
992 }
993
994 const size_t nargs = c.arguments().size();
995
996 if (found->second == Intrinsic::kSample) {
Brian Osman14d00962021-04-02 17:04:35 -0400997 // Sample is very special, the first argument is a child (shader/colorFilter), which can't
998 // be evaluated
Greg Danielc2cca5a2021-05-04 13:36:16 +0000999 const Context& ctx = *fProgram.fContext;
1000 if (nargs > 2 || !c.arguments()[0]->type().isEffectChild() ||
1001 (nargs == 2 && (c.arguments()[1]->type() != *ctx.fTypes.fFloat2 &&
1002 c.arguments()[1]->type() != *ctx.fTypes.fFloat3x3))) {
1003 SkDEBUGFAIL("Invalid call to sample");
1004 return {};
Brian Osman0a442b72020-12-02 11:12:51 -05001005 }
1006
Greg Danielc2cca5a2021-05-04 13:36:16 +00001007 auto fp_it = fVariableMap.find(c.arguments()[0]->as<VariableReference>().variable());
1008 SkASSERT(fp_it != fVariableMap.end());
1009
1010 skvm::Coord coord = fLocalCoord;
1011 if (nargs == 2) {
1012 Value arg = this->writeExpression(*c.arguments()[1]);
1013 SkASSERT(arg.slots() == 2);
1014 coord = {f32(arg[0]), f32(arg[1])};
1015 }
1016
1017 skvm::Color color = fSampleChild(fp_it->second, coord);
Brian Osman0a442b72020-12-02 11:12:51 -05001018 Value result(4);
1019 result[0] = color.r;
1020 result[1] = color.g;
1021 result[2] = color.b;
1022 result[3] = color.a;
1023 return result;
1024 }
1025
1026 const size_t kMaxArgs = 3; // eg: clamp, mix, smoothstep
1027 Value args[kMaxArgs];
1028 SkASSERT(nargs >= 1 && nargs <= SK_ARRAY_COUNT(args));
1029
1030 // All other intrinsics have at most three args, and those can all be evaluated up front:
1031 for (size_t i = 0; i < nargs; ++i) {
1032 args[i] = this->writeExpression(*c.arguments()[i]);
1033 }
1034 Type::NumberKind nk = base_number_kind(c.arguments()[0]->type());
1035
1036 auto binary = [&](auto&& fn) {
1037 // Binary intrinsics are (vecN, vecN), (vecN, float), or (float, vecN)
1038 size_t nslots = std::max(args[0].slots(), args[1].slots());
1039 Value result(nslots);
1040 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
1041 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
1042
1043 for (size_t i = 0; i < nslots; ++i) {
1044 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
1045 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]});
1046 }
1047 return result;
1048 };
1049
1050 auto ternary = [&](auto&& fn) {
1051 // Ternary intrinsics are some combination of vecN and float
1052 size_t nslots = std::max({args[0].slots(), args[1].slots(), args[2].slots()});
1053 Value result(nslots);
1054 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
1055 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
1056 SkASSERT(args[2].slots() == nslots || args[2].slots() == 1);
1057
1058 for (size_t i = 0; i < nslots; ++i) {
1059 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
1060 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]},
1061 {fBuilder, args[2][args[2].slots() == 1 ? 0 : i]});
1062 }
1063 return result;
1064 };
1065
1066 auto dot = [&](const Value& x, const Value& y) {
1067 SkASSERT(x.slots() == y.slots());
1068 skvm::F32 result = f32(x[0]) * f32(y[0]);
1069 for (size_t i = 1; i < x.slots(); ++i) {
1070 result += f32(x[i]) * f32(y[i]);
1071 }
1072 return result;
1073 };
1074
1075 switch (found->second) {
Brian Osman22cc3be2020-12-30 10:38:15 -05001076 case Intrinsic::kRadians:
1077 return unary(args[0], [](skvm::F32 deg) { return deg * (SK_FloatPI / 180); });
1078 case Intrinsic::kDegrees:
1079 return unary(args[0], [](skvm::F32 rad) { return rad * (180 / SK_FloatPI); });
1080
Brian Osman0a442b72020-12-02 11:12:51 -05001081 case Intrinsic::kSin: return unary(args[0], skvm::approx_sin);
1082 case Intrinsic::kCos: return unary(args[0], skvm::approx_cos);
1083 case Intrinsic::kTan: return unary(args[0], skvm::approx_tan);
1084
1085 case Intrinsic::kASin: return unary(args[0], skvm::approx_asin);
1086 case Intrinsic::kACos: return unary(args[0], skvm::approx_acos);
1087
1088 case Intrinsic::kATan: return nargs == 1 ? unary(args[0], skvm::approx_atan)
1089 : binary(skvm::approx_atan2);
1090
1091 case Intrinsic::kPow:
1092 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::approx_powf(x, y); });
1093 case Intrinsic::kExp: return unary(args[0], skvm::approx_exp);
1094 case Intrinsic::kLog: return unary(args[0], skvm::approx_log);
1095 case Intrinsic::kExp2: return unary(args[0], skvm::approx_pow2);
1096 case Intrinsic::kLog2: return unary(args[0], skvm::approx_log2);
1097
1098 case Intrinsic::kSqrt: return unary(args[0], skvm::sqrt);
1099 case Intrinsic::kInverseSqrt:
1100 return unary(args[0], [](skvm::F32 x) { return 1.0f / skvm::sqrt(x); });
1101
1102 case Intrinsic::kAbs: return unary(args[0], skvm::abs);
1103 case Intrinsic::kSign:
1104 return unary(args[0], [](skvm::F32 x) { return select(x < 0, -1.0f,
1105 select(x > 0, +1.0f, 0.0f)); });
1106 case Intrinsic::kFloor: return unary(args[0], skvm::floor);
1107 case Intrinsic::kCeil: return unary(args[0], skvm::ceil);
1108 case Intrinsic::kFract: return unary(args[0], skvm::fract);
1109 case Intrinsic::kMod:
1110 return binary([](skvm::F32 x, skvm::F32 y) { return x - y*skvm::floor(x / y); });
1111
1112 case Intrinsic::kMin:
1113 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::min(x, y); });
1114 case Intrinsic::kMax:
1115 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::max(x, y); });
1116 case Intrinsic::kClamp:
1117 return ternary(
1118 [](skvm::F32 x, skvm::F32 lo, skvm::F32 hi) { return skvm::clamp(x, lo, hi); });
1119 case Intrinsic::kSaturate:
1120 return unary(args[0], [](skvm::F32 x) { return skvm::clamp01(x); });
1121 case Intrinsic::kMix:
1122 return ternary(
1123 [](skvm::F32 x, skvm::F32 y, skvm::F32 t) { return skvm::lerp(x, y, t); });
1124 case Intrinsic::kStep:
1125 return binary([](skvm::F32 edge, skvm::F32 x) { return select(x < edge, 0.0f, 1.0f); });
1126 case Intrinsic::kSmoothstep:
1127 return ternary([](skvm::F32 edge0, skvm::F32 edge1, skvm::F32 x) {
1128 skvm::F32 t = skvm::clamp01((x - edge0) / (edge1 - edge0));
Mike Kleinff4decc2021-02-10 16:13:35 -06001129 return t ** t ** (3 - 2 ** t);
Brian Osman0a442b72020-12-02 11:12:51 -05001130 });
1131
1132 case Intrinsic::kLength: return skvm::sqrt(dot(args[0], args[0]));
1133 case Intrinsic::kDistance: {
1134 Value vec = binary([](skvm::F32 x, skvm::F32 y) { return x - y; });
1135 return skvm::sqrt(dot(vec, vec));
1136 }
1137 case Intrinsic::kDot: return dot(args[0], args[1]);
Brian Osman22cc3be2020-12-30 10:38:15 -05001138 case Intrinsic::kCross: {
1139 skvm::F32 ax = f32(args[0][0]), ay = f32(args[0][1]), az = f32(args[0][2]),
1140 bx = f32(args[1][0]), by = f32(args[1][1]), bz = f32(args[1][2]);
1141 Value result(3);
Mike Kleinff4decc2021-02-10 16:13:35 -06001142 result[0] = ay**bz - az**by;
1143 result[1] = az**bx - ax**bz;
1144 result[2] = ax**by - ay**bx;
Brian Osman22cc3be2020-12-30 10:38:15 -05001145 return result;
1146 }
Brian Osman0a442b72020-12-02 11:12:51 -05001147 case Intrinsic::kNormalize: {
1148 skvm::F32 invLen = 1.0f / skvm::sqrt(dot(args[0], args[0]));
Mike Kleinff4decc2021-02-10 16:13:35 -06001149 return unary(args[0], [&](skvm::F32 x) { return x ** invLen; });
Brian Osman0a442b72020-12-02 11:12:51 -05001150 }
Brian Osman22cc3be2020-12-30 10:38:15 -05001151 case Intrinsic::kFaceforward: {
1152 const Value &N = args[0],
1153 &I = args[1],
1154 &Nref = args[2];
1155
1156 skvm::F32 dotNrefI = dot(Nref, I);
1157 return unary(N, [&](skvm::F32 n) { return select(dotNrefI<0, n, -n); });
1158 }
1159 case Intrinsic::kReflect: {
1160 const Value &I = args[0],
1161 &N = args[1];
1162
1163 skvm::F32 dotNI = dot(N, I);
1164 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001165 return i - 2**dotNI**n;
Brian Osman22cc3be2020-12-30 10:38:15 -05001166 });
1167 }
1168 case Intrinsic::kRefract: {
1169 const Value &I = args[0],
1170 &N = args[1];
1171 skvm::F32 eta = f32(args[2]);
1172
1173 skvm::F32 dotNI = dot(N, I),
Mike Kleinff4decc2021-02-10 16:13:35 -06001174 k = 1 - eta**eta**(1 - dotNI**dotNI);
Brian Osman22cc3be2020-12-30 10:38:15 -05001175 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001176 return select(k<0, 0.0f, eta**i - (eta**dotNI + sqrt(k))**n);
Brian Osman22cc3be2020-12-30 10:38:15 -05001177 });
1178 }
Brian Osman0a442b72020-12-02 11:12:51 -05001179
Brian Osman93aed9a2020-12-28 15:18:46 -05001180 case Intrinsic::kMatrixCompMult:
Mike Kleinff4decc2021-02-10 16:13:35 -06001181 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001182 case Intrinsic::kInverse: {
1183 switch (args[0].slots()) {
1184 case 4: return this->writeMatrixInverse2x2(args[0]);
1185 case 9: return this->writeMatrixInverse3x3(args[0]);
1186 case 16: return this->writeMatrixInverse4x4(args[0]);
1187 default:
1188 SkDEBUGFAIL("Invalid call to inverse");
1189 return {};
1190 }
1191 }
1192
1193 case Intrinsic::kLessThan:
Brian Osman30b67292020-12-23 13:02:09 -05001194 return nk == Type::NumberKind::kFloat
1195 ? binary([](skvm::F32 x, skvm::F32 y) { return x < y; })
1196 : binary([](skvm::I32 x, skvm::I32 y) { return x < y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001197 case Intrinsic::kLessThanEqual:
Brian Osman30b67292020-12-23 13:02:09 -05001198 return nk == Type::NumberKind::kFloat
1199 ? binary([](skvm::F32 x, skvm::F32 y) { return x <= y; })
1200 : binary([](skvm::I32 x, skvm::I32 y) { return x <= y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001201 case Intrinsic::kGreaterThan:
Brian Osman30b67292020-12-23 13:02:09 -05001202 return nk == Type::NumberKind::kFloat
1203 ? binary([](skvm::F32 x, skvm::F32 y) { return x > y; })
1204 : binary([](skvm::I32 x, skvm::I32 y) { return x > y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001205 case Intrinsic::kGreaterThanEqual:
Brian Osman30b67292020-12-23 13:02:09 -05001206 return nk == Type::NumberKind::kFloat
1207 ? binary([](skvm::F32 x, skvm::F32 y) { return x >= y; })
1208 : binary([](skvm::I32 x, skvm::I32 y) { return x >= y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001209
1210 case Intrinsic::kEqual:
1211 return nk == Type::NumberKind::kFloat
1212 ? binary([](skvm::F32 x, skvm::F32 y) { return x == y; })
1213 : binary([](skvm::I32 x, skvm::I32 y) { return x == y; });
1214 case Intrinsic::kNotEqual:
1215 return nk == Type::NumberKind::kFloat
1216 ? binary([](skvm::F32 x, skvm::F32 y) { return x != y; })
1217 : binary([](skvm::I32 x, skvm::I32 y) { return x != y; });
1218
1219 case Intrinsic::kAny: {
1220 skvm::I32 result = i32(args[0][0]);
1221 for (size_t i = 1; i < args[0].slots(); ++i) {
1222 result |= i32(args[0][i]);
1223 }
1224 return result;
1225 }
1226 case Intrinsic::kAll: {
1227 skvm::I32 result = i32(args[0][0]);
1228 for (size_t i = 1; i < args[0].slots(); ++i) {
1229 result &= i32(args[0][i]);
1230 }
1231 return result;
1232 }
1233 case Intrinsic::kNot: return unary(args[0], [](skvm::I32 x) { return ~x; });
1234
1235 case Intrinsic::kSample:
1236 // Handled earlier
1237 SkASSERT(false);
1238 return {};
1239 }
1240 SkUNREACHABLE;
1241}
1242
1243Value SkVMGenerator::writeFunctionCall(const FunctionCall& f) {
Brian Osman54515b72021-01-07 14:38:08 -05001244 if (f.function().isBuiltin() && !f.function().definition()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001245 return this->writeIntrinsicCall(f);
1246 }
1247
Brian Osman54515b72021-01-07 14:38:08 -05001248 const FunctionDeclaration& decl = f.function();
1249
1250 // Evaluate all arguments, gather the results into a contiguous list of IDs
1251 std::vector<skvm::Val> argVals;
1252 for (const auto& arg : f.arguments()) {
1253 Value v = this->writeExpression(*arg);
1254 for (size_t i = 0; i < v.slots(); ++i) {
1255 argVals.push_back(v[i]);
1256 }
1257 }
1258
1259 // Create storage for the return value
John Stiles47b087e2021-04-06 13:19:35 -04001260 size_t nslots = f.type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001261 Value result(nslots);
1262 for (size_t i = 0; i < nslots; ++i) {
1263 result[i] = fBuilder->splat(0.0f);
1264 }
1265
1266 {
Brian Osman9333c872021-01-13 15:06:17 -05001267 // This merges currentFunction().fReturned into fConditionMask. Lanes that conditionally
Brian Osman54515b72021-01-07 14:38:08 -05001268 // returned in the current function would otherwise resume execution within the child.
Brian Osman9333c872021-01-13 15:06:17 -05001269 ScopedCondition m(this, ~currentFunction().fReturned);
Ethan Nicholas624a5292021-04-16 14:54:43 -04001270 SkASSERTF(f.function().definition(), "no definition for function '%s'",
1271 f.function().description().c_str());
Brian Osman54515b72021-01-07 14:38:08 -05001272 this->writeFunction(*f.function().definition(), argVals, result.asSpan());
1273 }
1274
1275 // Propagate new values of any 'out' params back to the original arguments
1276 const std::unique_ptr<Expression>* argIter = f.arguments().begin();
1277 size_t valIdx = 0;
1278 for (const Variable* p : decl.parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001279 size_t nslots = p->type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001280 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1281 Value v(nslots);
1282 for (size_t i = 0; i < nslots; ++i) {
1283 v[i] = argVals[valIdx + i];
1284 }
1285 const std::unique_ptr<Expression>& arg = *argIter;
1286 this->writeStore(*arg, v);
1287 }
1288 valIdx += nslots;
1289 argIter++;
1290 }
1291
1292 return result;
Brian Osman0a442b72020-12-02 11:12:51 -05001293}
1294
Brian Osmandd50b0c2021-01-11 17:04:29 -05001295Value SkVMGenerator::writeExternalFunctionCall(const ExternalFunctionCall& c) {
1296 // Evaluate all arguments, gather the results into a contiguous list of F32
1297 std::vector<skvm::F32> args;
1298 for (const auto& arg : c.arguments()) {
1299 Value v = this->writeExpression(*arg);
1300 for (size_t i = 0; i < v.slots(); ++i) {
1301 args.push_back(f32(v[i]));
1302 }
1303 }
1304
1305 // Create storage for the return value
John Stiles47b087e2021-04-06 13:19:35 -04001306 size_t nslots = c.type().slotCount();
Brian Osmandd50b0c2021-01-11 17:04:29 -05001307 std::vector<skvm::F32> result(nslots, fBuilder->splat(0.0f));
1308
1309 c.function().call(fBuilder, args.data(), result.data(), this->mask());
1310
1311 // Convert from 'vector of F32' to Value
1312 Value resultVal(nslots);
1313 for (size_t i = 0; i < nslots; ++i) {
1314 resultVal[i] = result[i];
1315 }
1316
1317 return resultVal;
1318}
1319
Brian Osman0a442b72020-12-02 11:12:51 -05001320Value SkVMGenerator::writePrefixExpression(const PrefixExpression& p) {
1321 Value val = this->writeExpression(*p.operand());
1322
John Stiles45990502021-02-16 10:55:27 -05001323 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001324 case Token::Kind::TK_PLUSPLUS:
1325 case Token::Kind::TK_MINUSMINUS: {
John Stiles45990502021-02-16 10:55:27 -05001326 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001327
1328 switch (base_number_kind(p.type())) {
1329 case Type::NumberKind::kFloat:
1330 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1331 break;
1332 case Type::NumberKind::kSigned:
1333 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1334 break;
1335 default:
1336 SkASSERT(false);
1337 return {};
1338 }
1339 return this->writeStore(*p.operand(), val);
1340 }
1341 case Token::Kind::TK_MINUS: {
1342 switch (base_number_kind(p.type())) {
1343 case Type::NumberKind::kFloat:
1344 return this->unary(val, [](skvm::F32 x) { return -x; });
1345 case Type::NumberKind::kSigned:
1346 return this->unary(val, [](skvm::I32 x) { return -x; });
1347 default:
1348 SkASSERT(false);
1349 return {};
1350 }
1351 }
1352 case Token::Kind::TK_LOGICALNOT:
1353 case Token::Kind::TK_BITWISENOT:
1354 return this->unary(val, [](skvm::I32 x) { return ~x; });
1355 default:
1356 SkASSERT(false);
1357 return {};
1358 }
1359}
1360
1361Value SkVMGenerator::writePostfixExpression(const PostfixExpression& p) {
John Stiles45990502021-02-16 10:55:27 -05001362 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001363 case Token::Kind::TK_PLUSPLUS:
1364 case Token::Kind::TK_MINUSMINUS: {
1365 Value old = this->writeExpression(*p.operand()),
1366 val = old;
1367 SkASSERT(val.slots() == 1);
John Stiles45990502021-02-16 10:55:27 -05001368 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001369
1370 switch (base_number_kind(p.type())) {
1371 case Type::NumberKind::kFloat:
1372 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1373 break;
1374 case Type::NumberKind::kSigned:
1375 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1376 break;
1377 default:
1378 SkASSERT(false);
1379 return {};
1380 }
1381 this->writeStore(*p.operand(), val);
1382 return old;
1383 }
1384 default:
1385 SkASSERT(false);
1386 return {};
1387 }
1388}
1389
1390Value SkVMGenerator::writeSwizzle(const Swizzle& s) {
1391 Value base = this->writeExpression(*s.base());
1392 Value swizzled(s.components().size());
1393 for (size_t i = 0; i < s.components().size(); ++i) {
1394 swizzled[i] = base[s.components()[i]];
1395 }
1396 return swizzled;
1397}
1398
1399Value SkVMGenerator::writeTernaryExpression(const TernaryExpression& t) {
1400 skvm::I32 test = i32(this->writeExpression(*t.test()));
1401 Value ifTrue, ifFalse;
1402
1403 {
Brian Osman9333c872021-01-13 15:06:17 -05001404 ScopedCondition m(this, test);
Brian Osman0a442b72020-12-02 11:12:51 -05001405 ifTrue = this->writeExpression(*t.ifTrue());
1406 }
1407 {
Brian Osman9333c872021-01-13 15:06:17 -05001408 ScopedCondition m(this, ~test);
Brian Osman0a442b72020-12-02 11:12:51 -05001409 ifFalse = this->writeExpression(*t.ifFalse());
1410 }
1411
1412 size_t nslots = ifTrue.slots();
1413 SkASSERT(nslots == ifFalse.slots());
1414
1415 Value result(nslots);
1416 for (size_t i = 0; i < nslots; ++i) {
1417 result[i] = skvm::select(test, i32(ifTrue[i]), i32(ifFalse[i]));
1418 }
1419 return result;
1420}
1421
1422Value SkVMGenerator::writeExpression(const Expression& e) {
1423 switch (e.kind()) {
1424 case Expression::Kind::kBinary:
1425 return this->writeBinaryExpression(e.as<BinaryExpression>());
1426 case Expression::Kind::kBoolLiteral:
1427 return fBuilder->splat(e.as<BoolLiteral>().value() ? ~0 : 0);
John Stiles7384b372021-04-01 13:48:15 -04001428 case Expression::Kind::kConstructorArray:
John Stiles8cad6372021-04-07 12:31:13 -04001429 case Expression::Kind::kConstructorCompound:
John Stilesd47330f2021-04-08 23:25:52 -04001430 case Expression::Kind::kConstructorStruct:
John Stilesd986f472021-04-06 15:54:43 -04001431 return this->writeAggregationConstructor(e.asAnyConstructor());
John Stilese1182782021-03-30 22:09:37 -04001432 case Expression::Kind::kConstructorDiagonalMatrix:
1433 return this->writeConstructorDiagonalMatrix(e.as<ConstructorDiagonalMatrix>());
John Stiles5abb9e12021-04-06 13:47:19 -04001434 case Expression::Kind::kConstructorMatrixResize:
1435 return this->writeConstructorMatrixResize(e.as<ConstructorMatrixResize>());
John Stilesfd7252f2021-04-04 22:24:40 -04001436 case Expression::Kind::kConstructorScalarCast:
John Stiles8cad6372021-04-07 12:31:13 -04001437 case Expression::Kind::kConstructorCompoundCast:
John Stilesb14a8192021-04-05 11:40:46 -04001438 return this->writeConstructorCast(e.asAnyConstructor());
John Stiles2938eea2021-04-01 18:58:25 -04001439 case Expression::Kind::kConstructorSplat:
1440 return this->writeConstructorSplat(e.as<ConstructorSplat>());
Brian Osman0a442b72020-12-02 11:12:51 -05001441 case Expression::Kind::kFieldAccess:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001442 return this->writeFieldAccess(e.as<FieldAccess>());
Brian Osman0a442b72020-12-02 11:12:51 -05001443 case Expression::Kind::kIndex:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001444 return this->writeIndexExpression(e.as<IndexExpression>());
Brian Osman0a442b72020-12-02 11:12:51 -05001445 case Expression::Kind::kVariableReference:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001446 return this->writeVariableExpression(e.as<VariableReference>());
Brian Osman0a442b72020-12-02 11:12:51 -05001447 case Expression::Kind::kFloatLiteral:
1448 return fBuilder->splat(e.as<FloatLiteral>().value());
1449 case Expression::Kind::kFunctionCall:
1450 return this->writeFunctionCall(e.as<FunctionCall>());
Brian Osmandd50b0c2021-01-11 17:04:29 -05001451 case Expression::Kind::kExternalFunctionCall:
1452 return this->writeExternalFunctionCall(e.as<ExternalFunctionCall>());
Brian Osman0a442b72020-12-02 11:12:51 -05001453 case Expression::Kind::kIntLiteral:
1454 return fBuilder->splat(static_cast<int>(e.as<IntLiteral>().value()));
Brian Osman0a442b72020-12-02 11:12:51 -05001455 case Expression::Kind::kPrefix:
1456 return this->writePrefixExpression(e.as<PrefixExpression>());
1457 case Expression::Kind::kPostfix:
1458 return this->writePostfixExpression(e.as<PostfixExpression>());
1459 case Expression::Kind::kSwizzle:
1460 return this->writeSwizzle(e.as<Swizzle>());
1461 case Expression::Kind::kTernary:
1462 return this->writeTernaryExpression(e.as<TernaryExpression>());
Brian Osmanbe0b3b72021-01-06 14:27:35 -05001463 case Expression::Kind::kExternalFunctionReference:
Brian Osman0a442b72020-12-02 11:12:51 -05001464 default:
1465 SkDEBUGFAIL("Unsupported expression");
1466 return {};
1467 }
1468}
1469
1470Value SkVMGenerator::writeStore(const Expression& lhs, const Value& rhs) {
John Stiles47b087e2021-04-06 13:19:35 -04001471 SkASSERTF(rhs.slots() == lhs.type().slotCount(),
John Stiles94e72b92021-01-30 11:06:18 -05001472 "lhs=%s (%s)\nrhs=%d slot",
1473 lhs.type().description().c_str(), lhs.description().c_str(), rhs.slots());
Brian Osman0a442b72020-12-02 11:12:51 -05001474
Brian Osman21f57072021-01-25 13:51:57 -05001475 // We need to figure out the collection of slots that we're storing into. The l-value (lhs)
1476 // is always a VariableReference, possibly wrapped by one or more Swizzle, FieldAccess, or
1477 // IndexExpressions. The underlying VariableReference has a range of slots for its storage,
1478 // and each expression wrapped around that selects a sub-set of those slots (Field/Index),
1479 // or rearranges them (Swizzle).
1480 SkSTArray<4, size_t, true> slots;
1481 slots.resize(rhs.slots());
1482
1483 // Start with the identity slot map - this basically says that the values from rhs belong in
1484 // slots [0, 1, 2 ... N] of the lhs.
1485 for (size_t i = 0; i < slots.size(); ++i) {
1486 slots[i] = i;
1487 }
1488
1489 // Now, as we peel off each outer expression, adjust 'slots' to be the locations relative to
1490 // the next (inner) expression:
1491 const Expression* expr = &lhs;
1492 while (!expr->is<VariableReference>()) {
1493 switch (expr->kind()) {
1494 case Expression::Kind::kFieldAccess: {
1495 const FieldAccess& fld = expr->as<FieldAccess>();
1496 size_t offset = this->fieldSlotOffset(fld);
1497 for (size_t& s : slots) {
1498 s += offset;
1499 }
1500 expr = fld.base().get();
1501 } break;
1502 case Expression::Kind::kIndex: {
1503 const IndexExpression& idx = expr->as<IndexExpression>();
1504 size_t offset = this->indexSlotOffset(idx);
1505 for (size_t& s : slots) {
1506 s += offset;
1507 }
1508 expr = idx.base().get();
1509 } break;
1510 case Expression::Kind::kSwizzle: {
1511 const Swizzle& swz = expr->as<Swizzle>();
1512 for (size_t& s : slots) {
1513 s = swz.components()[s];
1514 }
1515 expr = swz.base().get();
1516 } break;
1517 default:
1518 // No other kinds of expressions are valid in lvalues. (see Analysis::IsAssignable)
1519 SkDEBUGFAIL("Invalid expression type");
1520 return {};
1521 }
1522 }
1523
1524 // When we get here, 'slots' are all relative to the first slot holding 'var's storage
1525 const Variable& var = *expr->as<VariableReference>().variable();
1526 size_t varSlot = this->getSlot(var);
Brian Osman0a442b72020-12-02 11:12:51 -05001527 skvm::I32 mask = this->mask();
1528 for (size_t i = rhs.slots(); i --> 0;) {
John Stiles47b087e2021-04-06 13:19:35 -04001529 SkASSERT(slots[i] < var.type().slotCount());
Brian Osman21f57072021-01-25 13:51:57 -05001530 skvm::F32 curr = f32(fSlots[varSlot + slots[i]]),
Brian Osman0a442b72020-12-02 11:12:51 -05001531 next = f32(rhs[i]);
Brian Osman21f57072021-01-25 13:51:57 -05001532 fSlots[varSlot + slots[i]] = select(mask, next, curr).id;
Brian Osman0a442b72020-12-02 11:12:51 -05001533 }
1534 return rhs;
1535}
1536
1537void SkVMGenerator::writeBlock(const Block& b) {
1538 for (const std::unique_ptr<Statement>& stmt : b.children()) {
1539 this->writeStatement(*stmt);
1540 }
1541}
1542
Brian Osman9333c872021-01-13 15:06:17 -05001543void SkVMGenerator::writeBreakStatement() {
1544 // Any active lanes stop executing for the duration of the current loop
1545 fLoopMask &= ~this->mask();
1546}
1547
1548void SkVMGenerator::writeContinueStatement() {
1549 // Any active lanes stop executing for the current iteration.
1550 // Remember them in fContinueMask, to be re-enabled later.
1551 skvm::I32 mask = this->mask();
1552 fLoopMask &= ~mask;
1553 fContinueMask |= mask;
1554}
1555
1556void SkVMGenerator::writeForStatement(const ForStatement& f) {
1557 // We require that all loops be ES2-compliant (unrollable), and actually unroll them here
1558 Analysis::UnrollableLoopInfo loop;
John Stiles232b4ce2021-03-01 22:14:22 -05001559 SkAssertResult(Analysis::ForLoopIsValidForES2(f.fOffset, f.initializer().get(), f.test().get(),
1560 f.next().get(), f.statement().get(), &loop,
1561 /*errors=*/nullptr));
John Stiles47b087e2021-04-06 13:19:35 -04001562 SkASSERT(loop.fIndex->type().slotCount() == 1);
Brian Osman9333c872021-01-13 15:06:17 -05001563
Brian Osman21f57072021-01-25 13:51:57 -05001564 size_t indexSlot = this->getSlot(*loop.fIndex);
Brian Osman9333c872021-01-13 15:06:17 -05001565 double val = loop.fStart;
1566
1567 skvm::I32 oldLoopMask = fLoopMask,
1568 oldContinueMask = fContinueMask;
1569
1570 for (int i = 0; i < loop.fCount; ++i) {
Brian Osman21f57072021-01-25 13:51:57 -05001571 fSlots[indexSlot] = loop.fIndex->type().isInteger()
1572 ? fBuilder->splat(static_cast<int>(val)).id
1573 : fBuilder->splat(static_cast<float>(val)).id;
Brian Osman9333c872021-01-13 15:06:17 -05001574
1575 fContinueMask = fBuilder->splat(0);
1576 this->writeStatement(*f.statement());
1577 fLoopMask |= fContinueMask;
1578
1579 val += loop.fDelta;
1580 }
1581
1582 fLoopMask = oldLoopMask;
1583 fContinueMask = oldContinueMask;
1584}
1585
Brian Osman0a442b72020-12-02 11:12:51 -05001586void SkVMGenerator::writeIfStatement(const IfStatement& i) {
1587 Value test = this->writeExpression(*i.test());
1588 {
Brian Osman9333c872021-01-13 15:06:17 -05001589 ScopedCondition ifTrue(this, i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001590 this->writeStatement(*i.ifTrue());
1591 }
1592 if (i.ifFalse()) {
Brian Osman9333c872021-01-13 15:06:17 -05001593 ScopedCondition ifFalse(this, ~i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001594 this->writeStatement(*i.ifFalse());
1595 }
1596}
1597
1598void SkVMGenerator::writeReturnStatement(const ReturnStatement& r) {
Brian Osman54515b72021-01-07 14:38:08 -05001599 skvm::I32 returnsHere = this->mask();
Brian Osman0a442b72020-12-02 11:12:51 -05001600
Brian Osman54515b72021-01-07 14:38:08 -05001601 if (r.expression()) {
1602 Value val = this->writeExpression(*r.expression());
Brian Osman0a442b72020-12-02 11:12:51 -05001603
Brian Osman54515b72021-01-07 14:38:08 -05001604 int i = 0;
1605 for (skvm::Val& slot : currentFunction().fReturnValue) {
1606 slot = select(returnsHere, f32(val[i]), f32(slot)).id;
1607 i++;
1608 }
Brian Osman0a442b72020-12-02 11:12:51 -05001609 }
1610
Brian Osman54515b72021-01-07 14:38:08 -05001611 currentFunction().fReturned |= returnsHere;
Brian Osman0a442b72020-12-02 11:12:51 -05001612}
1613
1614void SkVMGenerator::writeVarDeclaration(const VarDeclaration& decl) {
Brian Osman21f57072021-01-25 13:51:57 -05001615 size_t slot = this->getSlot(decl.var()),
John Stiles47b087e2021-04-06 13:19:35 -04001616 nslots = decl.var().type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -05001617
1618 Value val = decl.value() ? this->writeExpression(*decl.value()) : Value{};
1619 for (size_t i = 0; i < nslots; ++i) {
1620 fSlots[slot + i] = val ? val[i] : fBuilder->splat(0.0f).id;
1621 }
1622}
1623
1624void SkVMGenerator::writeStatement(const Statement& s) {
1625 switch (s.kind()) {
1626 case Statement::Kind::kBlock:
1627 this->writeBlock(s.as<Block>());
1628 break;
Brian Osman9333c872021-01-13 15:06:17 -05001629 case Statement::Kind::kBreak:
1630 this->writeBreakStatement();
1631 break;
1632 case Statement::Kind::kContinue:
1633 this->writeContinueStatement();
1634 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001635 case Statement::Kind::kExpression:
1636 this->writeExpression(*s.as<ExpressionStatement>().expression());
1637 break;
Brian Osman9333c872021-01-13 15:06:17 -05001638 case Statement::Kind::kFor:
1639 this->writeForStatement(s.as<ForStatement>());
1640 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001641 case Statement::Kind::kIf:
1642 this->writeIfStatement(s.as<IfStatement>());
1643 break;
1644 case Statement::Kind::kReturn:
1645 this->writeReturnStatement(s.as<ReturnStatement>());
1646 break;
1647 case Statement::Kind::kVarDeclaration:
1648 this->writeVarDeclaration(s.as<VarDeclaration>());
1649 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001650 case Statement::Kind::kDiscard:
1651 case Statement::Kind::kDo:
Brian Osman0a442b72020-12-02 11:12:51 -05001652 case Statement::Kind::kSwitch:
Brian Osman57e353f2021-01-07 15:55:20 -05001653 SkDEBUGFAIL("Unsupported control flow");
Brian Osman0a442b72020-12-02 11:12:51 -05001654 break;
1655 case Statement::Kind::kInlineMarker:
1656 case Statement::Kind::kNop:
1657 break;
1658 default:
1659 SkASSERT(false);
1660 }
1661}
1662
1663skvm::Color ProgramToSkVM(const Program& program,
1664 const FunctionDefinition& function,
1665 skvm::Builder* builder,
1666 SkSpan<skvm::Val> uniforms,
1667 skvm::Coord device,
1668 skvm::Coord local,
Brian Osman577c6062021-04-12 17:17:19 -04001669 skvm::Color inputColor,
Brian Osman0a442b72020-12-02 11:12:51 -05001670 SampleChildFn sampleChild) {
Mike Kleinaebcf732021-01-14 10:15:00 -06001671 skvm::Val zero = builder->splat(0.0f).id;
1672 skvm::Val result[4] = {zero,zero,zero,zero};
Brian Osman577c6062021-04-12 17:17:19 -04001673
1674 skvm::Val args[6]; // At most 6 arguments (float2 coords, half4 inColor)
1675 size_t argSlots = 0;
Brian Osman0a442b72020-12-02 11:12:51 -05001676 for (const SkSL::Variable* param : function.declaration().parameters()) {
Brian Osman577c6062021-04-12 17:17:19 -04001677 switch (param->modifiers().fLayout.fBuiltin) {
1678 case SK_MAIN_COORDS_BUILTIN:
1679 SkASSERT(param->type().slotCount() == 2);
1680 args[argSlots++] = local.x.id;
1681 args[argSlots++] = local.y.id;
1682 break;
1683 case SK_INPUT_COLOR_BUILTIN:
1684 SkASSERT(param->type().slotCount() == 4);
1685 args[argSlots++] = inputColor.r.id;
1686 args[argSlots++] = inputColor.g.id;
1687 args[argSlots++] = inputColor.b.id;
1688 args[argSlots++] = inputColor.a.id;
1689 break;
1690 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
Greg Danielc2cca5a2021-05-04 13:36:16 +00001697 SkVMGenerator generator(program, builder, uniforms, device, local, std::move(sampleChild));
Brian Osman577c6062021-04-12 17:17:19 -04001698 generator.writeFunction(function, {args, argSlots}, result);
Brian Osman0a442b72020-12-02 11:12:51 -05001699
Brian Osman57e353f2021-01-07 15:55:20 -05001700 return skvm::Color{{builder, result[0]},
1701 {builder, result[1]},
1702 {builder, result[2]},
1703 {builder, result[3]}};
Brian Osman0a442b72020-12-02 11:12:51 -05001704}
1705
Brian Osmanf4a77732020-12-28 09:03:00 -05001706bool ProgramToSkVM(const Program& program,
1707 const FunctionDefinition& function,
1708 skvm::Builder* b,
Brian Osmanc92df392021-01-11 13:16:28 -05001709 SkSpan<skvm::Val> uniforms,
Brian Osmanf4a77732020-12-28 09:03:00 -05001710 SkVMSignature* outSignature) {
Brian Osmanf4a77732020-12-28 09:03:00 -05001711 SkVMSignature ignored,
1712 *signature = outSignature ? outSignature : &ignored;
1713
Mike Klein00e43df2021-01-08 13:45:42 -06001714 std::vector<skvm::Ptr> argPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001715 std::vector<skvm::Val> argVals;
1716
1717 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001718 size_t slots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001719 signature->fParameterSlots += slots;
1720 for (size_t i = 0; i < slots; ++i) {
1721 argPtrs.push_back(b->varying<float>());
1722 argVals.push_back(b->loadF(argPtrs.back()).id);
1723 }
1724 }
1725
Mike Klein00e43df2021-01-08 13:45:42 -06001726 std::vector<skvm::Ptr> returnPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001727 std::vector<skvm::Val> returnVals;
1728
John Stiles47b087e2021-04-06 13:19:35 -04001729 signature->fReturnSlots = function.declaration().returnType().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001730 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1731 returnPtrs.push_back(b->varying<float>());
1732 returnVals.push_back(b->splat(0.0f).id);
1733 }
1734
Greg Danielc2cca5a2021-05-04 13:36:16 +00001735 skvm::Coord zeroCoord = {b->splat(0.0f), b->splat(0.0f)};
Brian Osmanc92df392021-01-11 13:16:28 -05001736 SkVMGenerator generator(program, b, uniforms, /*device=*/zeroCoord, /*local=*/zeroCoord,
Greg Danielc2cca5a2021-05-04 13:36:16 +00001737 /*sampleChild=*/{});
Brian Osmandb2dad52021-01-07 14:08:30 -05001738 generator.writeFunction(function, argVals, returnVals);
Brian Osmanf4a77732020-12-28 09:03:00 -05001739
1740 // generateCode has updated the contents of 'argVals' for any 'out' or 'inout' parameters.
1741 // Propagate those changes back to our varying buffers:
1742 size_t argIdx = 0;
1743 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001744 size_t nslots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001745 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1746 for (size_t i = 0; i < nslots; ++i) {
1747 b->storeF(argPtrs[argIdx + i], skvm::F32{b, argVals[argIdx + i]});
1748 }
1749 }
1750 argIdx += nslots;
1751 }
1752
1753 // It's also updated the contents of 'returnVals' with the return value of the entry point.
1754 // Store that as well:
1755 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1756 b->storeF(returnPtrs[i], skvm::F32{b, returnVals[i]});
1757 }
1758
1759 return true;
1760}
1761
Brian Osman5933d4c2021-01-05 13:02:20 -05001762const FunctionDefinition* Program_GetFunction(const Program& program, const char* function) {
1763 for (const ProgramElement* e : program.elements()) {
1764 if (e->is<FunctionDefinition>() &&
1765 e->as<FunctionDefinition>().declaration().name() == function) {
1766 return &e->as<FunctionDefinition>();
1767 }
1768 }
1769 return nullptr;
1770}
1771
Brian Osmane89d8ea2021-01-20 14:01:30 -05001772static void gather_uniforms(UniformInfo* info, const Type& type, const String& name) {
1773 switch (type.typeKind()) {
1774 case Type::TypeKind::kStruct:
1775 for (const auto& f : type.fields()) {
1776 gather_uniforms(info, *f.fType, name + "." + f.fName);
1777 }
1778 break;
1779 case Type::TypeKind::kArray:
1780 for (int i = 0; i < type.columns(); ++i) {
1781 gather_uniforms(info, type.componentType(),
1782 String::printf("%s[%d]", name.c_str(), i));
1783 }
1784 break;
1785 case Type::TypeKind::kScalar:
1786 case Type::TypeKind::kVector:
1787 case Type::TypeKind::kMatrix:
1788 info->fUniforms.push_back({name, base_number_kind(type), type.rows(), type.columns(),
1789 info->fUniformSlotCount});
1790 info->fUniformSlotCount += type.columns() * type.rows();
1791 break;
1792 default:
1793 break;
1794 }
1795}
1796
1797std::unique_ptr<UniformInfo> Program_GetUniformInfo(const Program& program) {
1798 auto info = std::make_unique<UniformInfo>();
1799 for (const ProgramElement* e : program.elements()) {
1800 if (!e->is<GlobalVarDeclaration>()) {
1801 continue;
1802 }
1803 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1804 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
1805 if (var.modifiers().fFlags & Modifiers::kUniform_Flag) {
1806 gather_uniforms(info.get(), var.type(), var.name());
1807 }
1808 }
1809 return info;
1810}
1811
Brian Osman47726a12020-12-17 16:02:08 -05001812/*
1813 * Testing utility function that emits program's "main" with a minimal harness. Used to create
1814 * representative skvm op sequences for SkSL tests.
1815 */
1816bool testingOnly_ProgramToSkVMShader(const Program& program, skvm::Builder* builder) {
Brian Osman5933d4c2021-01-05 13:02:20 -05001817 const SkSL::FunctionDefinition* main = Program_GetFunction(program, "main");
1818 if (!main) {
1819 return false;
1820 }
1821
Brian Osman47726a12020-12-17 16:02:08 -05001822 size_t uniformSlots = 0;
1823 int childSlots = 0;
1824 for (const SkSL::ProgramElement* e : program.elements()) {
Brian Osman47726a12020-12-17 16:02:08 -05001825 if (e->is<GlobalVarDeclaration>()) {
1826 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1827 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
Brian Osman14d00962021-04-02 17:04:35 -04001828 if (var.type().isEffectChild()) {
Brian Osman47726a12020-12-17 16:02:08 -05001829 childSlots++;
1830 } else if (is_uniform(var)) {
John Stiles47b087e2021-04-06 13:19:35 -04001831 uniformSlots += var.type().slotCount();
Brian Osman47726a12020-12-17 16:02:08 -05001832 }
1833 }
1834 }
Brian Osman0a442b72020-12-02 11:12:51 -05001835
Mike Kleinae562bd2021-01-08 14:15:55 -06001836 skvm::Uniforms uniforms(builder->uniform(), 0);
Brian Osman47726a12020-12-17 16:02:08 -05001837
1838 auto new_uni = [&]() { return builder->uniformF(uniforms.pushF(0.0f)); };
1839
1840 // Assume identity CTM
1841 skvm::Coord device = {pun_to_F32(builder->index()), new_uni()};
1842 skvm::Coord local = device;
1843
1844 struct Child {
1845 skvm::Uniform addr;
1846 skvm::I32 rowBytesAsPixels;
1847 };
1848
1849 std::vector<Child> children;
1850 for (int i = 0; i < childSlots; ++i) {
1851 children.push_back({uniforms.pushPtr(nullptr), builder->uniform32(uniforms.push(0))});
1852 }
1853
Greg Danielc2cca5a2021-05-04 13:36:16 +00001854 auto sampleChild = [&](int i, skvm::Coord coord) {
Mike Klein447f3312021-02-08 09:46:59 -06001855 skvm::PixelFormat pixelFormat = skvm::SkColorType_to_PixelFormat(kRGBA_F32_SkColorType);
Brian Osman3f904db2021-01-28 13:24:31 -05001856 skvm::I32 index = trunc(coord.x);
1857 index += trunc(coord.y) * children[i].rowBytesAsPixels;
Brian Osman47726a12020-12-17 16:02:08 -05001858 return gather(pixelFormat, children[i].addr, index);
1859 };
1860
1861 std::vector<skvm::Val> uniformVals;
1862 for (size_t i = 0; i < uniformSlots; ++i) {
1863 uniformVals.push_back(new_uni().id);
1864 }
1865
Brian Osman577c6062021-04-12 17:17:19 -04001866 skvm::Color inColor = builder->uniformColor(SkColors::kWhite, &uniforms);
1867
1868 skvm::Color result = SkSL::ProgramToSkVM(
1869 program, *main, builder, uniformVals, device, local, inColor, sampleChild);
Brian Osman47726a12020-12-17 16:02:08 -05001870
1871 storeF(builder->varying<float>(), result.r);
1872 storeF(builder->varying<float>(), result.g);
1873 storeF(builder->varying<float>(), result.b);
1874 storeF(builder->varying<float>(), result.a);
1875
1876 return true;
1877
1878}
1879
1880} // namespace SkSL