blob: b9e2333532f9d9644f6168428e6a266600ed8232 [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 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"
33#include "src/sksl/ir/SkSLFloatLiteral.h"
34#include "src/sksl/ir/SkSLForStatement.h"
35#include "src/sksl/ir/SkSLFunctionCall.h"
36#include "src/sksl/ir/SkSLFunctionDeclaration.h"
37#include "src/sksl/ir/SkSLFunctionDefinition.h"
38#include "src/sksl/ir/SkSLIfStatement.h"
39#include "src/sksl/ir/SkSLIndexExpression.h"
40#include "src/sksl/ir/SkSLIntLiteral.h"
Brian Osman0a442b72020-12-02 11:12:51 -050041#include "src/sksl/ir/SkSLPostfixExpression.h"
42#include "src/sksl/ir/SkSLPrefixExpression.h"
Brian Osman0a442b72020-12-02 11:12:51 -050043#include "src/sksl/ir/SkSLReturnStatement.h"
Brian Osman0a442b72020-12-02 11:12:51 -050044#include "src/sksl/ir/SkSLSwitchStatement.h"
45#include "src/sksl/ir/SkSLSwizzle.h"
46#include "src/sksl/ir/SkSLTernaryExpression.h"
47#include "src/sksl/ir/SkSLVarDeclarations.h"
48#include "src/sksl/ir/SkSLVariableReference.h"
49
50#include <algorithm>
51#include <unordered_map>
52
Mike Kleinff4decc2021-02-10 16:13:35 -060053namespace {
54 // sksl allows the optimizations of fast_mul(), so we want to use that most of the time.
55 // This little sneaky snippet of code lets us use ** as a fast multiply infix operator.
56 struct FastF32 { skvm::F32 val; };
57 static FastF32 operator*(skvm::F32 y) { return {y}; }
58 static skvm::F32 operator*(skvm::F32 x, FastF32 y) { return fast_mul(x, y.val); }
59 static skvm::F32 operator*(float x, FastF32 y) { return fast_mul(x, y.val); }
60}
61
Brian Osman0a442b72020-12-02 11:12:51 -050062namespace SkSL {
63
64namespace {
65
Brian Osman0a442b72020-12-02 11:12:51 -050066// Holds scalars, vectors, or matrices
67struct Value {
68 Value() = default;
69 explicit Value(size_t slots) {
70 fVals.resize(slots);
71 }
72 Value(skvm::F32 x) : fVals({ x.id }) {}
73 Value(skvm::I32 x) : fVals({ x.id }) {}
74
75 explicit operator bool() const { return !fVals.empty(); }
76
77 size_t slots() const { return fVals.size(); }
78
79 struct ValRef {
80 ValRef(skvm::Val& val) : fVal(val) {}
81
82 ValRef& operator=(ValRef v) { fVal = v.fVal; return *this; }
83 ValRef& operator=(skvm::Val v) { fVal = v; return *this; }
84 ValRef& operator=(skvm::F32 v) { fVal = v.id; return *this; }
85 ValRef& operator=(skvm::I32 v) { fVal = v.id; return *this; }
86
87 operator skvm::Val() { return fVal; }
88
89 skvm::Val& fVal;
90 };
91
Brian Osmanf932c692021-01-26 13:54:07 -050092 ValRef operator[](size_t i) {
93 // These redundant asserts work around what we think is a codegen bug in GCC 8.x for
94 // 32-bit x86 Debug builds.
95 SkASSERT(i < fVals.size());
96 return fVals[i];
97 }
98 skvm::Val operator[](size_t i) const {
99 // These redundant asserts work around what we think is a codegen bug in GCC 8.x for
100 // 32-bit x86 Debug builds.
101 SkASSERT(i < fVals.size());
102 return fVals[i];
103 }
Brian Osman0a442b72020-12-02 11:12:51 -0500104
Brian Osmanae87bf12021-05-11 13:36:10 -0400105 SkSpan<skvm::Val> asSpan() { return SkMakeSpan(fVals); }
Brian Osman54515b72021-01-07 14:38:08 -0500106
Brian Osman0a442b72020-12-02 11:12:51 -0500107private:
108 SkSTArray<4, skvm::Val, true> fVals;
109};
110
111} // namespace
112
113class SkVMGenerator {
114public:
115 SkVMGenerator(const Program& program,
Brian Osman0a442b72020-12-02 11:12:51 -0500116 skvm::Builder* builder,
117 SkSpan<skvm::Val> uniforms,
Brian Osman0a442b72020-12-02 11:12:51 -0500118 skvm::Coord device,
119 skvm::Coord local,
John Stiles137482f2021-07-23 10:38:57 -0400120 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -0400121 SampleColorFilterFn sampleColorFilter,
122 SampleBlenderFn sampleBlender);
Brian Osman0a442b72020-12-02 11:12:51 -0500123
Brian Osmandb2dad52021-01-07 14:08:30 -0500124 void writeFunction(const FunctionDefinition& function,
125 SkSpan<skvm::Val> arguments,
126 SkSpan<skvm::Val> outReturn);
Brian Osman0a442b72020-12-02 11:12:51 -0500127
128private:
Brian Osman0a442b72020-12-02 11:12:51 -0500129 /**
130 * In SkSL, a Variable represents a named, typed value (along with qualifiers, etc).
Brian Osman21f57072021-01-25 13:51:57 -0500131 * Every Variable is mapped to one (or several, contiguous) indices into our vector of
Brian Osman0a442b72020-12-02 11:12:51 -0500132 * skvm::Val. Those skvm::Val entries hold the current actual value of that variable.
133 *
134 * NOTE: Conceptually, each Variable is just mapped to a Value. We could implement it that way,
Brian Osman21f57072021-01-25 13:51:57 -0500135 * (and eliminate the indirection), but it would add overhead for each Variable,
Brian Osman0a442b72020-12-02 11:12:51 -0500136 * and add additional (different) bookkeeping for things like lvalue-swizzles.
137 *
138 * Any time a variable appears in an expression, that's a VariableReference, which is a kind of
139 * Expression. Evaluating that VariableReference (or any other Expression) produces a Value,
140 * which is a set of skvm::Val. (This allows an Expression to produce a vector or matrix, in
141 * addition to a scalar).
142 *
Brian Osman21f57072021-01-25 13:51:57 -0500143 * For a VariableReference, producing a Value is straightforward - we get the slot of the
144 * Variable (from fVariableMap), use that to look up the current skvm::Vals holding the
145 * variable's contents, and construct a Value with those ids.
Brian Osman0a442b72020-12-02 11:12:51 -0500146 */
147
148 /**
Brian Osman21f57072021-01-25 13:51:57 -0500149 * Returns the slot holding v's Val(s). Allocates storage if this is first time 'v' is
Brian Osman0a442b72020-12-02 11:12:51 -0500150 * referenced. Compound variables (e.g. vectors) will consume more than one slot, with
151 * getSlot returning the start of the contiguous chunk of slots.
152 */
Brian Osman21f57072021-01-25 13:51:57 -0500153 size_t getSlot(const Variable& v);
Brian Osman0a442b72020-12-02 11:12:51 -0500154
Mike Kleinaebcf732021-01-14 10:15:00 -0600155 skvm::F32 f32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
156 skvm::I32 i32(skvm::Val id) { SkASSERT(id != skvm::NA); return {fBuilder, id}; }
Brian Osman0a442b72020-12-02 11:12:51 -0500157
158 // Shorthand for scalars
159 skvm::F32 f32(const Value& v) { SkASSERT(v.slots() == 1); return f32(v[0]); }
160 skvm::I32 i32(const Value& v) { SkASSERT(v.slots() == 1); return i32(v[0]); }
161
162 template <typename Fn>
163 Value unary(const Value& v, Fn&& fn) {
164 Value result(v.slots());
165 for (size_t i = 0; i < v.slots(); ++i) {
166 result[i] = fn({fBuilder, v[i]});
167 }
168 return result;
169 }
170
Brian Osman54515b72021-01-07 14:38:08 -0500171 skvm::I32 mask() {
172 // As we encounter (possibly conditional) return statements, fReturned is updated to store
173 // the lanes that have already returned. For the remainder of the current function, those
174 // lanes should be disabled.
Brian Osman9333c872021-01-13 15:06:17 -0500175 return fConditionMask & fLoopMask & ~currentFunction().fReturned;
Brian Osman54515b72021-01-07 14:38:08 -0500176 }
Brian Osman0a442b72020-12-02 11:12:51 -0500177
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500178 size_t fieldSlotOffset(const FieldAccess& expr);
179 size_t indexSlotOffset(const IndexExpression& expr);
180
Brian Osman0a442b72020-12-02 11:12:51 -0500181 Value writeExpression(const Expression& expr);
182 Value writeBinaryExpression(const BinaryExpression& b);
John Stilesd986f472021-04-06 15:54:43 -0400183 Value writeAggregationConstructor(const AnyConstructor& c);
John Stilese1182782021-03-30 22:09:37 -0400184 Value writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& c);
John Stiles5abb9e12021-04-06 13:47:19 -0400185 Value writeConstructorMatrixResize(const ConstructorMatrixResize& c);
John Stilesb14a8192021-04-05 11:40:46 -0400186 Value writeConstructorCast(const AnyConstructor& c);
John Stiles2938eea2021-04-01 18:58:25 -0400187 Value writeConstructorSplat(const ConstructorSplat& c);
Brian Osman0a442b72020-12-02 11:12:51 -0500188 Value writeFunctionCall(const FunctionCall& c);
Brian Osmandd50b0c2021-01-11 17:04:29 -0500189 Value writeExternalFunctionCall(const ExternalFunctionCall& c);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500190 Value writeFieldAccess(const FieldAccess& expr);
191 Value writeIndexExpression(const IndexExpression& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500192 Value writeIntrinsicCall(const FunctionCall& c);
193 Value writePostfixExpression(const PostfixExpression& p);
194 Value writePrefixExpression(const PrefixExpression& p);
195 Value writeSwizzle(const Swizzle& swizzle);
196 Value writeTernaryExpression(const TernaryExpression& t);
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500197 Value writeVariableExpression(const VariableReference& expr);
Brian Osman0a442b72020-12-02 11:12:51 -0500198
John Stilesfd7252f2021-04-04 22:24:40 -0400199 Value writeTypeConversion(const Value& src, Type::NumberKind srcKind, Type::NumberKind dstKind);
200
Brian Osman0a442b72020-12-02 11:12:51 -0500201 void writeStatement(const Statement& s);
202 void writeBlock(const Block& b);
Brian Osman9333c872021-01-13 15:06:17 -0500203 void writeBreakStatement();
204 void writeContinueStatement();
205 void writeForStatement(const ForStatement& f);
Brian Osman0a442b72020-12-02 11:12:51 -0500206 void writeIfStatement(const IfStatement& stmt);
207 void writeReturnStatement(const ReturnStatement& r);
208 void writeVarDeclaration(const VarDeclaration& decl);
209
210 Value writeStore(const Expression& lhs, const Value& rhs);
211
212 Value writeMatrixInverse2x2(const Value& m);
213 Value writeMatrixInverse3x3(const Value& m);
214 Value writeMatrixInverse4x4(const Value& m);
215
Brian Osmandb2dad52021-01-07 14:08:30 -0500216 //
217 // Global state for the lifetime of the generator:
218 //
Brian Osman0a442b72020-12-02 11:12:51 -0500219 const Program& fProgram;
Brian Osman0a442b72020-12-02 11:12:51 -0500220 skvm::Builder* fBuilder;
221
Brian Osman0a442b72020-12-02 11:12:51 -0500222 const skvm::Coord fLocalCoord;
John Stiles137482f2021-07-23 10:38:57 -0400223 const SampleShaderFn fSampleShader;
224 const SampleColorFilterFn fSampleColorFilter;
John Stiles2955c262021-07-23 15:51:05 -0400225 const SampleBlenderFn fSampleBlender;
Brian Osman0a442b72020-12-02 11:12:51 -0500226
227 // [Variable, first slot in fSlots]
Brian Osman21f57072021-01-25 13:51:57 -0500228 std::unordered_map<const Variable*, size_t> fVariableMap;
Brian Osmandb2dad52021-01-07 14:08:30 -0500229 std::vector<skvm::Val> fSlots;
Brian Osman0a442b72020-12-02 11:12:51 -0500230
Brian Osman9333c872021-01-13 15:06:17 -0500231 // Conditional execution mask (managed by ScopedCondition, and tied to control-flow scopes)
232 skvm::I32 fConditionMask;
233
234 // Similar: loop execution masks. Each loop starts with all lanes active (fLoopMask).
235 // 'break' disables a lane in fLoopMask until the loop finishes
236 // 'continue' disables a lane in fLoopMask, and sets fContinueMask to be re-enabled on the next
237 // iteration
238 skvm::I32 fLoopMask;
239 skvm::I32 fContinueMask;
Brian Osman54515b72021-01-07 14:38:08 -0500240
Brian Osmandb2dad52021-01-07 14:08:30 -0500241 //
242 // State that's local to the generation of a single function:
243 //
Brian Osman54515b72021-01-07 14:38:08 -0500244 struct Function {
245 const SkSpan<skvm::Val> fReturnValue;
246 skvm::I32 fReturned;
247 };
248 std::vector<Function> fFunctionStack;
249 Function& currentFunction() { return fFunctionStack.back(); }
Brian Osman0a442b72020-12-02 11:12:51 -0500250
Brian Osman9333c872021-01-13 15:06:17 -0500251 class ScopedCondition {
Brian Osman0a442b72020-12-02 11:12:51 -0500252 public:
Brian Osman9333c872021-01-13 15:06:17 -0500253 ScopedCondition(SkVMGenerator* generator, skvm::I32 mask)
254 : fGenerator(generator), fOldConditionMask(fGenerator->fConditionMask) {
255 fGenerator->fConditionMask &= mask;
Brian Osman0a442b72020-12-02 11:12:51 -0500256 }
257
Brian Osman9333c872021-01-13 15:06:17 -0500258 ~ScopedCondition() { fGenerator->fConditionMask = fOldConditionMask; }
Brian Osman0a442b72020-12-02 11:12:51 -0500259
260 private:
261 SkVMGenerator* fGenerator;
Brian Osman9333c872021-01-13 15:06:17 -0500262 skvm::I32 fOldConditionMask;
Brian Osman0a442b72020-12-02 11:12:51 -0500263 };
264};
265
266static Type::NumberKind base_number_kind(const Type& type) {
267 if (type.typeKind() == Type::TypeKind::kMatrix || type.typeKind() == Type::TypeKind::kVector) {
268 return base_number_kind(type.componentType());
269 }
270 return type.numberKind();
271}
272
273static inline bool is_uniform(const SkSL::Variable& var) {
274 return var.modifiers().fFlags & Modifiers::kUniform_Flag;
275}
276
Brian Osman0a442b72020-12-02 11:12:51 -0500277SkVMGenerator::SkVMGenerator(const Program& program,
Brian Osman0a442b72020-12-02 11:12:51 -0500278 skvm::Builder* builder,
279 SkSpan<skvm::Val> uniforms,
Brian Osman0a442b72020-12-02 11:12:51 -0500280 skvm::Coord device,
281 skvm::Coord local,
John Stiles137482f2021-07-23 10:38:57 -0400282 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -0400283 SampleColorFilterFn sampleColorFilter,
284 SampleBlenderFn sampleBlender)
Brian Osman0a442b72020-12-02 11:12:51 -0500285 : fProgram(program)
Brian Osman0a442b72020-12-02 11:12:51 -0500286 , fBuilder(builder)
287 , fLocalCoord(local)
John Stiles137482f2021-07-23 10:38:57 -0400288 , fSampleShader(std::move(sampleShader))
John Stiles2955c262021-07-23 15:51:05 -0400289 , fSampleColorFilter(std::move(sampleColorFilter))
290 , fSampleBlender(std::move(sampleBlender)) {
Brian Osman9333c872021-01-13 15:06:17 -0500291 fConditionMask = fLoopMask = fBuilder->splat(0xffff'ffff);
Brian Osman0a442b72020-12-02 11:12:51 -0500292
293 // Now, add storage for each global variable (including uniforms) to fSlots, and entries in
294 // fVariableMap to remember where every variable is stored.
295 const skvm::Val* uniformIter = uniforms.begin();
296 size_t fpCount = 0;
297 for (const ProgramElement* e : fProgram.elements()) {
298 if (e->is<GlobalVarDeclaration>()) {
Brian Osmanc0576692021-02-17 13:52:35 -0500299 const GlobalVarDeclaration& gvd = e->as<GlobalVarDeclaration>();
300 const VarDeclaration& decl = gvd.declaration()->as<VarDeclaration>();
301 const Variable& var = decl.var();
Brian Osman0a442b72020-12-02 11:12:51 -0500302 SkASSERT(fVariableMap.find(&var) == fVariableMap.end());
303
Brian Osman14d00962021-04-02 17:04:35 -0400304 // For most variables, fVariableMap stores an index into fSlots, but for children,
John Stiles2955c262021-07-23 15:51:05 -0400305 // fVariableMap stores the index to pass to fSample(Shader|ColorFilter|Blender)
Brian Osman14d00962021-04-02 17:04:35 -0400306 if (var.type().isEffectChild()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500307 fVariableMap[&var] = fpCount++;
308 continue;
309 }
310
311 // Opaque types include fragment processors, GL objects (samplers, textures, etc), and
312 // special types like 'void'. Of those, only fragment processors are legal variables.
313 SkASSERT(!var.type().isOpaque());
314
Brian Osmanc0576692021-02-17 13:52:35 -0500315 // getSlot() allocates space for the variable's value in fSlots, initializes it to zero,
316 // and populates fVariableMap.
317 size_t slot = this->getSlot(var),
John Stiles47b087e2021-04-06 13:19:35 -0400318 nslots = var.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500319
320 if (int builtin = var.modifiers().fLayout.fBuiltin; builtin >= 0) {
321 // builtin variables are system-defined, with special semantics. The only builtin
322 // variable exposed to runtime effects is sk_FragCoord.
323 switch (builtin) {
324 case SK_FRAGCOORD_BUILTIN:
325 SkASSERT(nslots == 4);
Brian Osmanc0576692021-02-17 13:52:35 -0500326 fSlots[slot + 0] = device.x.id;
327 fSlots[slot + 1] = device.y.id;
328 fSlots[slot + 2] = fBuilder->splat(0.0f).id;
329 fSlots[slot + 3] = fBuilder->splat(1.0f).id;
Brian Osman0a442b72020-12-02 11:12:51 -0500330 break;
331 default:
332 SkDEBUGFAIL("Unsupported builtin");
333 }
334 } else if (is_uniform(var)) {
335 // For uniforms, copy the supplied IDs over
336 SkASSERT(uniformIter + nslots <= uniforms.end());
Brian Osmanc0576692021-02-17 13:52:35 -0500337 std::copy(uniformIter, uniformIter + nslots, fSlots.begin() + slot);
Brian Osman0a442b72020-12-02 11:12:51 -0500338 uniformIter += nslots;
Brian Osmanc0576692021-02-17 13:52:35 -0500339 } else if (decl.value()) {
340 // For other globals, populate with the initializer expression (if there is one)
341 Value val = this->writeExpression(*decl.value());
342 for (size_t i = 0; i < nslots; ++i) {
343 fSlots[slot + i] = val[i];
344 }
Brian Osman0a442b72020-12-02 11:12:51 -0500345 }
346 }
347 }
348 SkASSERT(uniformIter == uniforms.end());
Brian Osman0a442b72020-12-02 11:12:51 -0500349}
350
Brian Osmandb2dad52021-01-07 14:08:30 -0500351void SkVMGenerator::writeFunction(const FunctionDefinition& function,
352 SkSpan<skvm::Val> arguments,
353 SkSpan<skvm::Val> outReturn) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500354 const FunctionDeclaration& decl = function.declaration();
John Stiles47b087e2021-04-06 13:19:35 -0400355 SkASSERT(decl.returnType().slotCount() == outReturn.size());
Brian Osmandb2dad52021-01-07 14:08:30 -0500356
Brian Osman54515b72021-01-07 14:38:08 -0500357 fFunctionStack.push_back({outReturn, /*returned=*/fBuilder->splat(0)});
Brian Osmandb2dad52021-01-07 14:08:30 -0500358
359 // For all parameters, copy incoming argument IDs to our vector of (all) variable IDs
Brian Osman5933d4c2021-01-05 13:02:20 -0500360 size_t argIdx = 0;
Brian Osmandb2dad52021-01-07 14:08:30 -0500361 for (const Variable* p : decl.parameters()) {
Brian Osman21f57072021-01-25 13:51:57 -0500362 size_t paramSlot = this->getSlot(*p),
John Stiles47b087e2021-04-06 13:19:35 -0400363 nslots = p->type().slotCount();
Brian Osman5933d4c2021-01-05 13:02:20 -0500364
Brian Osmandb2dad52021-01-07 14:08:30 -0500365 for (size_t i = 0; i < nslots; ++i) {
366 fSlots[paramSlot + i] = arguments[argIdx + i];
367 }
368 argIdx += nslots;
369 }
370 SkASSERT(argIdx == arguments.size());
371
372 this->writeStatement(*function.body());
373
374 // Copy 'out' and 'inout' parameters back to their caller-supplied argument storage
375 argIdx = 0;
376 for (const Variable* p : decl.parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -0400377 size_t nslots = p->type().slotCount();
Brian Osmandb2dad52021-01-07 14:08:30 -0500378
Brian Osman5933d4c2021-01-05 13:02:20 -0500379 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
Brian Osman21f57072021-01-25 13:51:57 -0500380 size_t paramSlot = this->getSlot(*p);
Brian Osman5933d4c2021-01-05 13:02:20 -0500381 for (size_t i = 0; i < nslots; ++i) {
Brian Osmandb2dad52021-01-07 14:08:30 -0500382 arguments[argIdx + i] = fSlots[paramSlot + i];
Brian Osman5933d4c2021-01-05 13:02:20 -0500383 }
384 }
385 argIdx += nslots;
386 }
Brian Osmandb2dad52021-01-07 14:08:30 -0500387 SkASSERT(argIdx == arguments.size());
Brian Osman54515b72021-01-07 14:38:08 -0500388
389 fFunctionStack.pop_back();
Brian Osman0a442b72020-12-02 11:12:51 -0500390}
391
Brian Osman21f57072021-01-25 13:51:57 -0500392size_t SkVMGenerator::getSlot(const Variable& v) {
Brian Osman0a442b72020-12-02 11:12:51 -0500393 auto entry = fVariableMap.find(&v);
394 if (entry != fVariableMap.end()) {
395 return entry->second;
396 }
397
Brian Osman0a442b72020-12-02 11:12:51 -0500398 size_t slot = fSlots.size(),
John Stiles47b087e2021-04-06 13:19:35 -0400399 nslots = v.type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -0500400 fSlots.resize(slot + nslots, fBuilder->splat(0.0f).id);
401 fVariableMap[&v] = slot;
402 return slot;
403}
404
Brian Osman0a442b72020-12-02 11:12:51 -0500405Value SkVMGenerator::writeBinaryExpression(const BinaryExpression& b) {
406 const Expression& left = *b.left();
407 const Expression& right = *b.right();
John Stiles45990502021-02-16 10:55:27 -0500408 Operator op = b.getOperator();
409 if (op.kind() == Token::Kind::TK_EQ) {
Brian Osman0a442b72020-12-02 11:12:51 -0500410 return this->writeStore(left, this->writeExpression(right));
411 }
412
413 const Type& lType = left.type();
414 const Type& rType = right.type();
415 bool lVecOrMtx = (lType.isVector() || lType.isMatrix());
416 bool rVecOrMtx = (rType.isVector() || rType.isMatrix());
John Stiles45990502021-02-16 10:55:27 -0500417 bool isAssignment = op.isAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500418 if (isAssignment) {
John Stiles45990502021-02-16 10:55:27 -0500419 op = op.removeAssignment();
Brian Osman0a442b72020-12-02 11:12:51 -0500420 }
421 Type::NumberKind nk = base_number_kind(lType);
422
423 // A few ops require special treatment:
John Stiles45990502021-02-16 10:55:27 -0500424 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500425 case Token::Kind::TK_LOGICALAND: {
426 SkASSERT(!isAssignment);
427 SkASSERT(nk == Type::NumberKind::kBoolean);
428 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500429 ScopedCondition shortCircuit(this, lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500430 skvm::I32 rVal = i32(this->writeExpression(right));
431 return lVal & rVal;
432 }
433 case Token::Kind::TK_LOGICALOR: {
434 SkASSERT(!isAssignment);
435 SkASSERT(nk == Type::NumberKind::kBoolean);
436 skvm::I32 lVal = i32(this->writeExpression(left));
Brian Osman9333c872021-01-13 15:06:17 -0500437 ScopedCondition shortCircuit(this, ~lVal);
Brian Osman0a442b72020-12-02 11:12:51 -0500438 skvm::I32 rVal = i32(this->writeExpression(right));
439 return lVal | rVal;
440 }
John Stiles94e72b92021-01-30 11:06:18 -0500441 case Token::Kind::TK_COMMA:
442 // We write the left side of the expression to preserve its side effects, even though we
443 // immediately discard the result.
444 this->writeExpression(left);
445 return this->writeExpression(right);
Brian Osman0a442b72020-12-02 11:12:51 -0500446 default:
447 break;
448 }
449
450 // All of the other ops always evaluate both sides of the expression
451 Value lVal = this->writeExpression(left),
452 rVal = this->writeExpression(right);
453
454 // Special case for M*V, V*M, M*M (but not V*V!)
John Stiles45990502021-02-16 10:55:27 -0500455 if (op.kind() == Token::Kind::TK_STAR
Brian Osman0a442b72020-12-02 11:12:51 -0500456 && lVecOrMtx && rVecOrMtx && !(lType.isVector() && rType.isVector())) {
457 int rCols = rType.columns(),
458 rRows = rType.rows(),
459 lCols = lType.columns(),
460 lRows = lType.rows();
461 // M*V treats the vector as a column
462 if (rType.isVector()) {
463 std::swap(rCols, rRows);
464 }
465 SkASSERT(lCols == rRows);
John Stiles47b087e2021-04-06 13:19:35 -0400466 SkASSERT(b.type().slotCount() == static_cast<size_t>(lRows * rCols));
Brian Osman0a442b72020-12-02 11:12:51 -0500467 Value result(lRows * rCols);
468 size_t resultIdx = 0;
469 for (int c = 0; c < rCols; ++c)
470 for (int r = 0; r < lRows; ++r) {
471 skvm::F32 sum = fBuilder->splat(0.0f);
472 for (int j = 0; j < lCols; ++j) {
473 sum += f32(lVal[j*lRows + r]) * f32(rVal[c*rRows + j]);
474 }
475 result[resultIdx++] = sum;
476 }
477 SkASSERT(resultIdx == result.slots());
478 return isAssignment ? this->writeStore(left, result) : result;
479 }
480
481 size_t nslots = std::max(lVal.slots(), rVal.slots());
482
Brian Osman0a442b72020-12-02 11:12:51 -0500483 auto binary = [&](auto&& f_fn, auto&& i_fn) {
484 Value result(nslots);
485 for (size_t i = 0; i < nslots; ++i) {
486 // If one side is scalar, replicate it to all channels
487 skvm::Val L = lVal.slots() == 1 ? lVal[0] : lVal[i],
488 R = rVal.slots() == 1 ? rVal[0] : rVal[i];
489 if (nk == Type::NumberKind::kFloat) {
490 result[i] = f_fn(f32(L), f32(R));
491 } else {
492 result[i] = i_fn(i32(L), i32(R));
493 }
494 }
495 return isAssignment ? this->writeStore(left, result) : result;
496 };
497
498 auto unsupported_f = [&](skvm::F32, skvm::F32) {
499 SkDEBUGFAIL("Unsupported operator");
500 return skvm::F32{};
501 };
502
John Stiles45990502021-02-16 10:55:27 -0500503 switch (op.kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -0500504 case Token::Kind::TK_EQEQ: {
505 SkASSERT(!isAssignment);
506 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x == y; },
507 [](skvm::I32 x, skvm::I32 y) { return x == y; });
508 skvm::I32 folded = i32(cmp[0]);
509 for (size_t i = 1; i < nslots; ++i) {
510 folded &= i32(cmp[i]);
511 }
512 return folded;
513 }
514 case Token::Kind::TK_NEQ: {
515 SkASSERT(!isAssignment);
516 Value cmp = binary([](skvm::F32 x, skvm::F32 y) { return x != y; },
517 [](skvm::I32 x, skvm::I32 y) { return x != y; });
518 skvm::I32 folded = i32(cmp[0]);
519 for (size_t i = 1; i < nslots; ++i) {
520 folded |= i32(cmp[i]);
521 }
522 return folded;
523 }
524 case Token::Kind::TK_GT:
525 return binary([](skvm::F32 x, skvm::F32 y) { return x > y; },
526 [](skvm::I32 x, skvm::I32 y) { return x > y; });
527 case Token::Kind::TK_GTEQ:
528 return binary([](skvm::F32 x, skvm::F32 y) { return x >= y; },
529 [](skvm::I32 x, skvm::I32 y) { return x >= y; });
530 case Token::Kind::TK_LT:
531 return binary([](skvm::F32 x, skvm::F32 y) { return x < y; },
532 [](skvm::I32 x, skvm::I32 y) { return x < y; });
533 case Token::Kind::TK_LTEQ:
534 return binary([](skvm::F32 x, skvm::F32 y) { return x <= y; },
535 [](skvm::I32 x, skvm::I32 y) { return x <= y; });
536
537 case Token::Kind::TK_PLUS:
538 return binary([](skvm::F32 x, skvm::F32 y) { return x + y; },
539 [](skvm::I32 x, skvm::I32 y) { return x + y; });
540 case Token::Kind::TK_MINUS:
541 return binary([](skvm::F32 x, skvm::F32 y) { return x - y; },
542 [](skvm::I32 x, skvm::I32 y) { return x - y; });
543 case Token::Kind::TK_STAR:
Mike Kleinff4decc2021-02-10 16:13:35 -0600544 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; },
Brian Osman0a442b72020-12-02 11:12:51 -0500545 [](skvm::I32 x, skvm::I32 y) { return x * y; });
546 case Token::Kind::TK_SLASH:
547 // Minimum spec (GLSL ES 1.0) has very loose requirements for integer operations.
548 // (Low-end GPUs may not have integer ALUs). Given that, we are allowed to do floating
549 // point division plus rounding. Section 10.28 of the spec even clarifies that the
550 // rounding mode is undefined (but round-towards-zero is the obvious/common choice).
551 return binary([](skvm::F32 x, skvm::F32 y) { return x / y; },
552 [](skvm::I32 x, skvm::I32 y) {
553 return skvm::trunc(skvm::to_F32(x) / skvm::to_F32(y));
554 });
555
556 case Token::Kind::TK_BITWISEXOR:
557 case Token::Kind::TK_LOGICALXOR:
558 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x ^ y; });
559 case Token::Kind::TK_BITWISEAND:
560 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x & y; });
561 case Token::Kind::TK_BITWISEOR:
562 return binary(unsupported_f, [](skvm::I32 x, skvm::I32 y) { return x | y; });
563
564 // These three operators are all 'reserved' (illegal) in our minimum spec, but will require
565 // implementation in the future.
566 case Token::Kind::TK_PERCENT:
567 case Token::Kind::TK_SHL:
568 case Token::Kind::TK_SHR:
569 default:
570 SkDEBUGFAIL("Unsupported operator");
571 return {};
572 }
573}
574
John Stilesd986f472021-04-06 15:54:43 -0400575Value SkVMGenerator::writeAggregationConstructor(const AnyConstructor& c) {
John Stiles47b087e2021-04-06 13:19:35 -0400576 Value result(c.type().slotCount());
John Stiles626b62e2021-03-31 22:06:07 -0400577 size_t resultIdx = 0;
John Stilesd986f472021-04-06 15:54:43 -0400578 for (const auto &arg : c.argumentSpan()) {
John Stiles626b62e2021-03-31 22:06:07 -0400579 Value tmp = this->writeExpression(*arg);
580 for (size_t tmpSlot = 0; tmpSlot < tmp.slots(); ++tmpSlot) {
581 result[resultIdx++] = tmp[tmpSlot];
582 }
583 }
584 return result;
585}
586
John Stilesfd7252f2021-04-04 22:24:40 -0400587Value SkVMGenerator::writeTypeConversion(const Value& src,
588 Type::NumberKind srcKind,
589 Type::NumberKind dstKind) {
590 // Conversion among "similar" types (floatN <-> halfN), (shortN <-> intN), etc. is a no-op.
591 if (srcKind == dstKind) {
592 return src;
593 }
594
595 // TODO: Handle signed vs. unsigned. GLSL ES 1.0 only has 'int', so no problem yet.
596 Value dst(src.slots());
597 switch (dstKind) {
598 case Type::NumberKind::kFloat:
599 if (srcKind == Type::NumberKind::kSigned) {
600 // int -> float
601 for (size_t i = 0; i < src.slots(); ++i) {
602 dst[i] = skvm::to_F32(i32(src[i]));
603 }
604 return dst;
605 }
606 if (srcKind == Type::NumberKind::kBoolean) {
607 // bool -> float
608 for (size_t i = 0; i < src.slots(); ++i) {
609 dst[i] = skvm::select(i32(src[i]), 1.0f, 0.0f);
610 }
611 return dst;
612 }
613 break;
614
615 case Type::NumberKind::kSigned:
616 if (srcKind == Type::NumberKind::kFloat) {
617 // float -> int
618 for (size_t i = 0; i < src.slots(); ++i) {
619 dst[i] = skvm::trunc(f32(src[i]));
620 }
621 return dst;
622 }
623 if (srcKind == Type::NumberKind::kBoolean) {
624 // bool -> int
625 for (size_t i = 0; i < src.slots(); ++i) {
626 dst[i] = skvm::select(i32(src[i]), 1, 0);
627 }
628 return dst;
629 }
630 break;
631
632 case Type::NumberKind::kBoolean:
633 if (srcKind == Type::NumberKind::kSigned) {
634 // int -> bool
635 for (size_t i = 0; i < src.slots(); ++i) {
636 dst[i] = i32(src[i]) != 0;
637 }
638 return dst;
639 }
640 if (srcKind == Type::NumberKind::kFloat) {
641 // float -> bool
642 for (size_t i = 0; i < src.slots(); ++i) {
643 dst[i] = f32(src[i]) != 0.0;
644 }
645 return dst;
646 }
647 break;
648
649 default:
650 break;
651 }
John Stiles7bf79992021-06-25 11:05:20 -0400652 SkDEBUGFAILF("Unsupported type conversion: %d -> %d", (int)srcKind, (int)dstKind);
John Stilesfd7252f2021-04-04 22:24:40 -0400653 return {};
654}
655
John Stilesb14a8192021-04-05 11:40:46 -0400656Value SkVMGenerator::writeConstructorCast(const AnyConstructor& c) {
657 auto arguments = c.argumentSpan();
658 SkASSERT(arguments.size() == 1);
659 const Expression& argument = *arguments.front();
660
661 const Type& srcType = argument.type();
John Stilesfd7252f2021-04-04 22:24:40 -0400662 const Type& dstType = c.type();
663 Type::NumberKind srcKind = base_number_kind(srcType);
664 Type::NumberKind dstKind = base_number_kind(dstType);
John Stilesb14a8192021-04-05 11:40:46 -0400665 Value src = this->writeExpression(argument);
John Stilesfd7252f2021-04-04 22:24:40 -0400666 return this->writeTypeConversion(src, srcKind, dstKind);
667}
668
John Stiles2938eea2021-04-01 18:58:25 -0400669Value SkVMGenerator::writeConstructorSplat(const ConstructorSplat& c) {
670 SkASSERT(c.type().isVector());
671 SkASSERT(c.argument()->type().isScalar());
672 int columns = c.type().columns();
673
674 // Splat the argument across all components of a vector.
675 Value src = this->writeExpression(*c.argument());
676 Value dst(columns);
677 for (int i = 0; i < columns; ++i) {
678 dst[i] = src[0];
679 }
680 return dst;
681}
682
John Stiles68f56062021-08-03 12:31:56 -0400683Value SkVMGenerator::writeConstructorDiagonalMatrix(const ConstructorDiagonalMatrix& ctor) {
684 const Type& dstType = ctor.type();
John Stilese1182782021-03-30 22:09:37 -0400685 SkASSERT(dstType.isMatrix());
John Stiles68f56062021-08-03 12:31:56 -0400686 SkASSERT(ctor.argument()->type() == dstType.componentType());
John Stilese1182782021-03-30 22:09:37 -0400687
John Stiles68f56062021-08-03 12:31:56 -0400688 Value src = this->writeExpression(*ctor.argument());
John Stilese1182782021-03-30 22:09:37 -0400689 Value dst(dstType.rows() * dstType.columns());
690 size_t dstIndex = 0;
691
692 // Matrix-from-scalar builds a diagonal scale matrix
693 for (int c = 0; c < dstType.columns(); ++c) {
694 for (int r = 0; r < dstType.rows(); ++r) {
695 dst[dstIndex++] = (c == r ? f32(src) : fBuilder->splat(0.0f));
696 }
697 }
698
699 SkASSERT(dstIndex == dst.slots());
700 return dst;
701}
702
John Stiles68f56062021-08-03 12:31:56 -0400703Value SkVMGenerator::writeConstructorMatrixResize(const ConstructorMatrixResize& ctor) {
704 const Type& srcType = ctor.argument()->type();
705 const Type& dstType = ctor.type();
706 Value src = this->writeExpression(*ctor.argument());
John Stiles5abb9e12021-04-06 13:47:19 -0400707 Value dst(dstType.rows() * dstType.columns());
708
709 // Matrix-from-matrix uses src where it overlaps, and fills in missing fields with identity.
710 size_t dstIndex = 0;
711 for (int c = 0; c < dstType.columns(); ++c) {
712 for (int r = 0; r < dstType.rows(); ++r) {
713 if (c < srcType.columns() && r < srcType.rows()) {
714 dst[dstIndex++] = src[c * srcType.rows() + r];
715 } else {
716 dst[dstIndex++] = fBuilder->splat(c == r ? 1.0f : 0.0f);
717 }
718 }
719 }
720
721 SkASSERT(dstIndex == dst.slots());
722 return dst;
723}
724
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500725size_t SkVMGenerator::fieldSlotOffset(const FieldAccess& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500726 size_t offset = 0;
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500727 for (int i = 0; i < expr.fieldIndex(); ++i) {
John Stiles47b087e2021-04-06 13:19:35 -0400728 offset += (*expr.base()->type().fields()[i].fType).slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500729 }
730 return offset;
731}
732
733Value SkVMGenerator::writeFieldAccess(const FieldAccess& expr) {
734 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400735 Value field(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500736 size_t offset = this->fieldSlotOffset(expr);
737 for (size_t i = 0; i < field.slots(); ++i) {
738 field[i] = base[offset + i];
739 }
740 return field;
741}
742
743size_t SkVMGenerator::indexSlotOffset(const IndexExpression& expr) {
744 Value index = this->writeExpression(*expr.index());
745 int indexValue = -1;
746 SkAssertResult(fBuilder->allImm(index[0], &indexValue));
747
748 // When indexing by a literal, the front-end guarantees that we don't go out of bounds.
749 // But when indexing by a loop variable, it's possible to generate out-of-bounds access.
750 // The GLSL spec leaves that behavior undefined - we'll just clamp everything here.
751 indexValue = SkTPin(indexValue, 0, expr.base()->type().columns() - 1);
752
John Stiles47b087e2021-04-06 13:19:35 -0400753 size_t stride = expr.type().slotCount();
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500754 return indexValue * stride;
755}
756
757Value SkVMGenerator::writeIndexExpression(const IndexExpression& expr) {
758 Value base = this->writeExpression(*expr.base());
John Stiles47b087e2021-04-06 13:19:35 -0400759 Value element(expr.type().slotCount());
Brian Osmanfa71ffa2021-01-26 14:05:31 -0500760 size_t offset = this->indexSlotOffset(expr);
761 for (size_t i = 0; i < element.slots(); ++i) {
762 element[i] = base[offset + i];
763 }
764 return element;
765}
766
767Value SkVMGenerator::writeVariableExpression(const VariableReference& expr) {
Brian Osman21f57072021-01-25 13:51:57 -0500768 size_t slot = this->getSlot(*expr.variable());
John Stiles47b087e2021-04-06 13:19:35 -0400769 Value val(expr.type().slotCount());
Brian Osman0a442b72020-12-02 11:12:51 -0500770 for (size_t i = 0; i < val.slots(); ++i) {
771 val[i] = fSlots[slot + i];
772 }
773 return val;
774}
775
776Value SkVMGenerator::writeMatrixInverse2x2(const Value& m) {
777 SkASSERT(m.slots() == 4);
778 skvm::F32 a = f32(m[0]),
779 b = f32(m[1]),
780 c = f32(m[2]),
781 d = f32(m[3]);
782 skvm::F32 idet = 1.0f / (a*d - b*c);
783
784 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600785 result[0] = ( d ** idet);
786 result[1] = (-b ** idet);
787 result[2] = (-c ** idet);
788 result[3] = ( a ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500789 return result;
790}
791
792Value SkVMGenerator::writeMatrixInverse3x3(const Value& m) {
793 SkASSERT(m.slots() == 9);
794 skvm::F32 a11 = f32(m[0]), a12 = f32(m[3]), a13 = f32(m[6]),
795 a21 = f32(m[1]), a22 = f32(m[4]), a23 = f32(m[7]),
796 a31 = f32(m[2]), a32 = f32(m[5]), a33 = f32(m[8]);
797 skvm::F32 idet = 1.0f / (a11*a22*a33 + a12*a23*a31 + a13*a21*a32 -
798 a11*a23*a32 - a12*a21*a33 - a13*a22*a31);
799
800 Value result(m.slots());
Mike Kleinff4decc2021-02-10 16:13:35 -0600801 result[0] = ((a22**a33 - a23**a32) ** idet);
802 result[1] = ((a23**a31 - a21**a33) ** idet);
803 result[2] = ((a21**a32 - a22**a31) ** idet);
804 result[3] = ((a13**a32 - a12**a33) ** idet);
805 result[4] = ((a11**a33 - a13**a31) ** idet);
806 result[5] = ((a12**a31 - a11**a32) ** idet);
807 result[6] = ((a12**a23 - a13**a22) ** idet);
808 result[7] = ((a13**a21 - a11**a23) ** idet);
809 result[8] = ((a11**a22 - a12**a21) ** idet);
Brian Osman0a442b72020-12-02 11:12:51 -0500810 return result;
811}
812
813Value SkVMGenerator::writeMatrixInverse4x4(const Value& m) {
814 SkASSERT(m.slots() == 16);
815 skvm::F32 a00 = f32(m[0]), a10 = f32(m[4]), a20 = f32(m[ 8]), a30 = f32(m[12]),
816 a01 = f32(m[1]), a11 = f32(m[5]), a21 = f32(m[ 9]), a31 = f32(m[13]),
817 a02 = f32(m[2]), a12 = f32(m[6]), a22 = f32(m[10]), a32 = f32(m[14]),
818 a03 = f32(m[3]), a13 = f32(m[7]), a23 = f32(m[11]), a33 = f32(m[15]);
819
Mike Kleinff4decc2021-02-10 16:13:35 -0600820 skvm::F32 b00 = a00**a11 - a01**a10,
821 b01 = a00**a12 - a02**a10,
822 b02 = a00**a13 - a03**a10,
823 b03 = a01**a12 - a02**a11,
824 b04 = a01**a13 - a03**a11,
825 b05 = a02**a13 - a03**a12,
826 b06 = a20**a31 - a21**a30,
827 b07 = a20**a32 - a22**a30,
828 b08 = a20**a33 - a23**a30,
829 b09 = a21**a32 - a22**a31,
830 b10 = a21**a33 - a23**a31,
831 b11 = a22**a33 - a23**a32;
Brian Osman0a442b72020-12-02 11:12:51 -0500832
Mike Kleinff4decc2021-02-10 16:13:35 -0600833 skvm::F32 idet = 1.0f / (b00**b11 - b01**b10 + b02**b09 + b03**b08 - b04**b07 + b05**b06);
Brian Osman0a442b72020-12-02 11:12:51 -0500834
835 b00 *= idet;
836 b01 *= idet;
837 b02 *= idet;
838 b03 *= idet;
839 b04 *= idet;
840 b05 *= idet;
841 b06 *= idet;
842 b07 *= idet;
843 b08 *= idet;
844 b09 *= idet;
845 b10 *= idet;
846 b11 *= idet;
847
848 Value result(m.slots());
849 result[ 0] = (a11*b11 - a12*b10 + a13*b09);
850 result[ 1] = (a02*b10 - a01*b11 - a03*b09);
851 result[ 2] = (a31*b05 - a32*b04 + a33*b03);
852 result[ 3] = (a22*b04 - a21*b05 - a23*b03);
853 result[ 4] = (a12*b08 - a10*b11 - a13*b07);
854 result[ 5] = (a00*b11 - a02*b08 + a03*b07);
855 result[ 6] = (a32*b02 - a30*b05 - a33*b01);
856 result[ 7] = (a20*b05 - a22*b02 + a23*b01);
857 result[ 8] = (a10*b10 - a11*b08 + a13*b06);
858 result[ 9] = (a01*b08 - a00*b10 - a03*b06);
859 result[10] = (a30*b04 - a31*b02 + a33*b00);
860 result[11] = (a21*b02 - a20*b04 - a23*b00);
861 result[12] = (a11*b07 - a10*b09 - a12*b06);
862 result[13] = (a00*b09 - a01*b07 + a02*b06);
863 result[14] = (a31*b01 - a30*b03 - a32*b00);
864 result[15] = (a20*b03 - a21*b01 + a22*b00);
865 return result;
866}
867
868Value SkVMGenerator::writeIntrinsicCall(const FunctionCall& c) {
John Stiles032fcba2021-05-06 11:33:08 -0400869 IntrinsicKind intrinsicKind = c.function().intrinsicKind();
870 SkASSERT(intrinsicKind != kNotIntrinsic);
Brian Osman0a442b72020-12-02 11:12:51 -0500871
872 const size_t nargs = c.arguments().size();
873
John Stiles032fcba2021-05-06 11:33:08 -0400874 if (intrinsicKind == k_sample_IntrinsicKind) {
John Stilesbb2ef922021-07-26 08:32:07 -0400875 // Sample is very special. The first argument is a child (shader/colorFilter/blender),
876 // which is opaque and can't be evaluated.
John Stilesce9a5c92021-07-30 11:20:19 -0400877 SkASSERT(nargs >= 2);
Brian Osmanc9125aa2021-04-21 09:57:19 -0400878 const Expression* child = c.arguments()[0].get();
879 SkASSERT(child->type().isEffectChild());
880 SkASSERT(child->is<VariableReference>());
Brian Osman0a442b72020-12-02 11:12:51 -0500881
Brian Osmanc9125aa2021-04-21 09:57:19 -0400882 auto fp_it = fVariableMap.find(child->as<VariableReference>().variable());
Greg Danielc2cca5a2021-05-04 13:36:16 +0000883 SkASSERT(fp_it != fVariableMap.end());
884
Brian Osmanc9125aa2021-04-21 09:57:19 -0400885 // Shaders require a coordinate argument. Color filters require a color argument.
886 // When we call sampleChild, the other value remains the incoming default.
Brian Osmanc9125aa2021-04-21 09:57:19 -0400887 const Expression* arg = c.arguments()[1].get();
888 Value argVal = this->writeExpression(*arg);
John Stiles137482f2021-07-23 10:38:57 -0400889 skvm::Color color;
Brian Osmanc9125aa2021-04-21 09:57:19 -0400890
John Stilesce9a5c92021-07-30 11:20:19 -0400891 switch (child->type().typeKind()) {
892 case Type::TypeKind::kShader: {
893 SkASSERT(nargs == 2);
894 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fFloat2);
895 skvm::Coord coord = {f32(argVal[0]), f32(argVal[1])};
896 color = fSampleShader(fp_it->second, coord);
897 break;
898 }
899 case Type::TypeKind::kColorFilter: {
900 SkASSERT(nargs == 2);
901 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
902 arg->type() == *fProgram.fContext->fTypes.fFloat4);
903 skvm::Color inColor = {f32(argVal[0]), f32(argVal[1]),
904 f32(argVal[2]), f32(argVal[3])};
905 color = fSampleColorFilter(fp_it->second, inColor);
906 break;
907 }
908 case Type::TypeKind::kBlender: {
909 SkASSERT(nargs == 3);
910 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
911 arg->type() == *fProgram.fContext->fTypes.fFloat4);
912 skvm::Color srcColor = {f32(argVal[0]), f32(argVal[1]),
913 f32(argVal[2]), f32(argVal[3])};
914
915 arg = c.arguments()[2].get();
916 argVal = this->writeExpression(*arg);
917 SkASSERT(arg->type() == *fProgram.fContext->fTypes.fHalf4 ||
918 arg->type() == *fProgram.fContext->fTypes.fFloat4);
919 skvm::Color dstColor = {f32(argVal[0]), f32(argVal[1]),
920 f32(argVal[2]), f32(argVal[3])};
921
922 color = fSampleBlender(fp_it->second, srcColor, dstColor);
923 break;
924 }
925 default: {
926 SkDEBUGFAILF("cannot sample from type '%s'", child->type().description().c_str());
927 }
Greg Danielc2cca5a2021-05-04 13:36:16 +0000928 }
929
Brian Osman0a442b72020-12-02 11:12:51 -0500930 Value result(4);
931 result[0] = color.r;
932 result[1] = color.g;
933 result[2] = color.b;
934 result[3] = color.a;
935 return result;
936 }
937
938 const size_t kMaxArgs = 3; // eg: clamp, mix, smoothstep
939 Value args[kMaxArgs];
940 SkASSERT(nargs >= 1 && nargs <= SK_ARRAY_COUNT(args));
941
942 // All other intrinsics have at most three args, and those can all be evaluated up front:
943 for (size_t i = 0; i < nargs; ++i) {
944 args[i] = this->writeExpression(*c.arguments()[i]);
945 }
946 Type::NumberKind nk = base_number_kind(c.arguments()[0]->type());
947
948 auto binary = [&](auto&& fn) {
949 // Binary intrinsics are (vecN, vecN), (vecN, float), or (float, vecN)
950 size_t nslots = std::max(args[0].slots(), args[1].slots());
951 Value result(nslots);
952 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
953 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
954
955 for (size_t i = 0; i < nslots; ++i) {
956 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
957 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]});
958 }
959 return result;
960 };
961
962 auto ternary = [&](auto&& fn) {
963 // Ternary intrinsics are some combination of vecN and float
964 size_t nslots = std::max({args[0].slots(), args[1].slots(), args[2].slots()});
965 Value result(nslots);
966 SkASSERT(args[0].slots() == nslots || args[0].slots() == 1);
967 SkASSERT(args[1].slots() == nslots || args[1].slots() == 1);
968 SkASSERT(args[2].slots() == nslots || args[2].slots() == 1);
969
970 for (size_t i = 0; i < nslots; ++i) {
971 result[i] = fn({fBuilder, args[0][args[0].slots() == 1 ? 0 : i]},
972 {fBuilder, args[1][args[1].slots() == 1 ? 0 : i]},
973 {fBuilder, args[2][args[2].slots() == 1 ? 0 : i]});
974 }
975 return result;
976 };
977
978 auto dot = [&](const Value& x, const Value& y) {
979 SkASSERT(x.slots() == y.slots());
980 skvm::F32 result = f32(x[0]) * f32(y[0]);
981 for (size_t i = 1; i < x.slots(); ++i) {
982 result += f32(x[i]) * f32(y[i]);
983 }
984 return result;
985 };
986
John Stiles032fcba2021-05-06 11:33:08 -0400987 switch (intrinsicKind) {
988 case k_radians_IntrinsicKind:
Brian Osman22cc3be2020-12-30 10:38:15 -0500989 return unary(args[0], [](skvm::F32 deg) { return deg * (SK_FloatPI / 180); });
John Stiles032fcba2021-05-06 11:33:08 -0400990 case k_degrees_IntrinsicKind:
Brian Osman22cc3be2020-12-30 10:38:15 -0500991 return unary(args[0], [](skvm::F32 rad) { return rad * (180 / SK_FloatPI); });
992
John Stiles032fcba2021-05-06 11:33:08 -0400993 case k_sin_IntrinsicKind: return unary(args[0], skvm::approx_sin);
994 case k_cos_IntrinsicKind: return unary(args[0], skvm::approx_cos);
995 case k_tan_IntrinsicKind: return unary(args[0], skvm::approx_tan);
Brian Osman0a442b72020-12-02 11:12:51 -0500996
John Stiles032fcba2021-05-06 11:33:08 -0400997 case k_asin_IntrinsicKind: return unary(args[0], skvm::approx_asin);
998 case k_acos_IntrinsicKind: return unary(args[0], skvm::approx_acos);
Brian Osman0a442b72020-12-02 11:12:51 -0500999
John Stiles032fcba2021-05-06 11:33:08 -04001000 case k_atan_IntrinsicKind: return nargs == 1 ? unary(args[0], skvm::approx_atan)
Brian Osman0a442b72020-12-02 11:12:51 -05001001 : binary(skvm::approx_atan2);
1002
John Stiles032fcba2021-05-06 11:33:08 -04001003 case k_pow_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001004 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::approx_powf(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001005 case k_exp_IntrinsicKind: return unary(args[0], skvm::approx_exp);
1006 case k_log_IntrinsicKind: return unary(args[0], skvm::approx_log);
1007 case k_exp2_IntrinsicKind: return unary(args[0], skvm::approx_pow2);
1008 case k_log2_IntrinsicKind: return unary(args[0], skvm::approx_log2);
Brian Osman0a442b72020-12-02 11:12:51 -05001009
John Stiles032fcba2021-05-06 11:33:08 -04001010 case k_sqrt_IntrinsicKind: return unary(args[0], skvm::sqrt);
1011 case k_inversesqrt_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001012 return unary(args[0], [](skvm::F32 x) { return 1.0f / skvm::sqrt(x); });
1013
John Stiles032fcba2021-05-06 11:33:08 -04001014 case k_abs_IntrinsicKind: return unary(args[0], skvm::abs);
1015 case k_sign_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001016 return unary(args[0], [](skvm::F32 x) { return select(x < 0, -1.0f,
1017 select(x > 0, +1.0f, 0.0f)); });
John Stiles032fcba2021-05-06 11:33:08 -04001018 case k_floor_IntrinsicKind: return unary(args[0], skvm::floor);
1019 case k_ceil_IntrinsicKind: return unary(args[0], skvm::ceil);
1020 case k_fract_IntrinsicKind: return unary(args[0], skvm::fract);
1021 case k_mod_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001022 return binary([](skvm::F32 x, skvm::F32 y) { return x - y*skvm::floor(x / y); });
1023
John Stiles032fcba2021-05-06 11:33:08 -04001024 case k_min_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001025 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::min(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001026 case k_max_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001027 return binary([](skvm::F32 x, skvm::F32 y) { return skvm::max(x, y); });
John Stiles032fcba2021-05-06 11:33:08 -04001028 case k_clamp_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001029 return ternary(
1030 [](skvm::F32 x, skvm::F32 lo, skvm::F32 hi) { return skvm::clamp(x, lo, hi); });
John Stiles032fcba2021-05-06 11:33:08 -04001031 case k_saturate_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001032 return unary(args[0], [](skvm::F32 x) { return skvm::clamp01(x); });
John Stiles032fcba2021-05-06 11:33:08 -04001033 case k_mix_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001034 return ternary(
1035 [](skvm::F32 x, skvm::F32 y, skvm::F32 t) { return skvm::lerp(x, y, t); });
John Stiles032fcba2021-05-06 11:33:08 -04001036 case k_step_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001037 return binary([](skvm::F32 edge, skvm::F32 x) { return select(x < edge, 0.0f, 1.0f); });
John Stiles032fcba2021-05-06 11:33:08 -04001038 case k_smoothstep_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001039 return ternary([](skvm::F32 edge0, skvm::F32 edge1, skvm::F32 x) {
1040 skvm::F32 t = skvm::clamp01((x - edge0) / (edge1 - edge0));
Mike Kleinff4decc2021-02-10 16:13:35 -06001041 return t ** t ** (3 - 2 ** t);
Brian Osman0a442b72020-12-02 11:12:51 -05001042 });
1043
John Stiles032fcba2021-05-06 11:33:08 -04001044 case k_length_IntrinsicKind: return skvm::sqrt(dot(args[0], args[0]));
1045 case k_distance_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001046 Value vec = binary([](skvm::F32 x, skvm::F32 y) { return x - y; });
1047 return skvm::sqrt(dot(vec, vec));
1048 }
John Stiles032fcba2021-05-06 11:33:08 -04001049 case k_dot_IntrinsicKind: return dot(args[0], args[1]);
1050 case k_cross_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001051 skvm::F32 ax = f32(args[0][0]), ay = f32(args[0][1]), az = f32(args[0][2]),
1052 bx = f32(args[1][0]), by = f32(args[1][1]), bz = f32(args[1][2]);
1053 Value result(3);
Mike Kleinff4decc2021-02-10 16:13:35 -06001054 result[0] = ay**bz - az**by;
1055 result[1] = az**bx - ax**bz;
1056 result[2] = ax**by - ay**bx;
Brian Osman22cc3be2020-12-30 10:38:15 -05001057 return result;
1058 }
John Stiles032fcba2021-05-06 11:33:08 -04001059 case k_normalize_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001060 skvm::F32 invLen = 1.0f / skvm::sqrt(dot(args[0], args[0]));
Mike Kleinff4decc2021-02-10 16:13:35 -06001061 return unary(args[0], [&](skvm::F32 x) { return x ** invLen; });
Brian Osman0a442b72020-12-02 11:12:51 -05001062 }
John Stiles032fcba2021-05-06 11:33:08 -04001063 case k_faceforward_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001064 const Value &N = args[0],
1065 &I = args[1],
1066 &Nref = args[2];
1067
1068 skvm::F32 dotNrefI = dot(Nref, I);
1069 return unary(N, [&](skvm::F32 n) { return select(dotNrefI<0, n, -n); });
1070 }
John Stiles032fcba2021-05-06 11:33:08 -04001071 case k_reflect_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001072 const Value &I = args[0],
1073 &N = args[1];
1074
1075 skvm::F32 dotNI = dot(N, I);
1076 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001077 return i - 2**dotNI**n;
Brian Osman22cc3be2020-12-30 10:38:15 -05001078 });
1079 }
John Stiles032fcba2021-05-06 11:33:08 -04001080 case k_refract_IntrinsicKind: {
Brian Osman22cc3be2020-12-30 10:38:15 -05001081 const Value &I = args[0],
1082 &N = args[1];
1083 skvm::F32 eta = f32(args[2]);
1084
1085 skvm::F32 dotNI = dot(N, I),
Mike Kleinff4decc2021-02-10 16:13:35 -06001086 k = 1 - eta**eta**(1 - dotNI**dotNI);
Brian Osman22cc3be2020-12-30 10:38:15 -05001087 return binary([&](skvm::F32 i, skvm::F32 n) {
Mike Kleinff4decc2021-02-10 16:13:35 -06001088 return select(k<0, 0.0f, eta**i - (eta**dotNI + sqrt(k))**n);
Brian Osman22cc3be2020-12-30 10:38:15 -05001089 });
1090 }
Brian Osman0a442b72020-12-02 11:12:51 -05001091
John Stiles032fcba2021-05-06 11:33:08 -04001092 case k_matrixCompMult_IntrinsicKind:
Mike Kleinff4decc2021-02-10 16:13:35 -06001093 return binary([](skvm::F32 x, skvm::F32 y) { return x ** y; });
John Stiles032fcba2021-05-06 11:33:08 -04001094 case k_inverse_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001095 switch (args[0].slots()) {
1096 case 4: return this->writeMatrixInverse2x2(args[0]);
1097 case 9: return this->writeMatrixInverse3x3(args[0]);
1098 case 16: return this->writeMatrixInverse4x4(args[0]);
1099 default:
1100 SkDEBUGFAIL("Invalid call to inverse");
1101 return {};
1102 }
1103 }
1104
John Stiles032fcba2021-05-06 11:33:08 -04001105 case k_lessThan_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001106 return nk == Type::NumberKind::kFloat
1107 ? binary([](skvm::F32 x, skvm::F32 y) { return x < y; })
1108 : binary([](skvm::I32 x, skvm::I32 y) { return x < y; });
John Stiles032fcba2021-05-06 11:33:08 -04001109 case k_lessThanEqual_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001110 return nk == Type::NumberKind::kFloat
1111 ? binary([](skvm::F32 x, skvm::F32 y) { return x <= y; })
1112 : binary([](skvm::I32 x, skvm::I32 y) { return x <= y; });
John Stiles032fcba2021-05-06 11:33:08 -04001113 case k_greaterThan_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001114 return nk == Type::NumberKind::kFloat
1115 ? binary([](skvm::F32 x, skvm::F32 y) { return x > y; })
1116 : binary([](skvm::I32 x, skvm::I32 y) { return x > y; });
John Stiles032fcba2021-05-06 11:33:08 -04001117 case k_greaterThanEqual_IntrinsicKind:
Brian Osman30b67292020-12-23 13:02:09 -05001118 return nk == Type::NumberKind::kFloat
1119 ? binary([](skvm::F32 x, skvm::F32 y) { return x >= y; })
1120 : binary([](skvm::I32 x, skvm::I32 y) { return x >= y; });
Brian Osman0a442b72020-12-02 11:12:51 -05001121
John Stiles032fcba2021-05-06 11:33:08 -04001122 case k_equal_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001123 return nk == Type::NumberKind::kFloat
1124 ? binary([](skvm::F32 x, skvm::F32 y) { return x == y; })
1125 : binary([](skvm::I32 x, skvm::I32 y) { return x == y; });
John Stiles032fcba2021-05-06 11:33:08 -04001126 case k_notEqual_IntrinsicKind:
Brian Osman0a442b72020-12-02 11:12:51 -05001127 return nk == Type::NumberKind::kFloat
1128 ? binary([](skvm::F32 x, skvm::F32 y) { return x != y; })
1129 : binary([](skvm::I32 x, skvm::I32 y) { return x != y; });
1130
John Stiles032fcba2021-05-06 11:33:08 -04001131 case k_any_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001132 skvm::I32 result = i32(args[0][0]);
1133 for (size_t i = 1; i < args[0].slots(); ++i) {
1134 result |= i32(args[0][i]);
1135 }
1136 return result;
1137 }
John Stiles032fcba2021-05-06 11:33:08 -04001138 case k_all_IntrinsicKind: {
Brian Osman0a442b72020-12-02 11:12:51 -05001139 skvm::I32 result = i32(args[0][0]);
1140 for (size_t i = 1; i < args[0].slots(); ++i) {
1141 result &= i32(args[0][i]);
1142 }
1143 return result;
1144 }
John Stiles032fcba2021-05-06 11:33:08 -04001145 case k_not_IntrinsicKind: return unary(args[0], [](skvm::I32 x) { return ~x; });
Brian Osman0a442b72020-12-02 11:12:51 -05001146
John Stiles032fcba2021-05-06 11:33:08 -04001147 default:
1148 SkDEBUGFAILF("unsupported intrinsic %s", c.function().description().c_str());
Brian Osman0a442b72020-12-02 11:12:51 -05001149 return {};
1150 }
1151 SkUNREACHABLE;
1152}
1153
1154Value SkVMGenerator::writeFunctionCall(const FunctionCall& f) {
John Stiles032fcba2021-05-06 11:33:08 -04001155 if (f.function().isIntrinsic() && !f.function().definition()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001156 return this->writeIntrinsicCall(f);
1157 }
1158
Brian Osman54515b72021-01-07 14:38:08 -05001159 const FunctionDeclaration& decl = f.function();
1160
1161 // Evaluate all arguments, gather the results into a contiguous list of IDs
1162 std::vector<skvm::Val> argVals;
1163 for (const auto& arg : f.arguments()) {
1164 Value v = this->writeExpression(*arg);
1165 for (size_t i = 0; i < v.slots(); ++i) {
1166 argVals.push_back(v[i]);
1167 }
1168 }
1169
1170 // Create storage for the return value
John Stiles47b087e2021-04-06 13:19:35 -04001171 size_t nslots = f.type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001172 Value result(nslots);
1173 for (size_t i = 0; i < nslots; ++i) {
1174 result[i] = fBuilder->splat(0.0f);
1175 }
1176
1177 {
Brian Osman9333c872021-01-13 15:06:17 -05001178 // This merges currentFunction().fReturned into fConditionMask. Lanes that conditionally
Brian Osman54515b72021-01-07 14:38:08 -05001179 // returned in the current function would otherwise resume execution within the child.
Brian Osman9333c872021-01-13 15:06:17 -05001180 ScopedCondition m(this, ~currentFunction().fReturned);
Ethan Nicholas624a5292021-04-16 14:54:43 -04001181 SkASSERTF(f.function().definition(), "no definition for function '%s'",
1182 f.function().description().c_str());
Brian Osmanae87bf12021-05-11 13:36:10 -04001183 this->writeFunction(*f.function().definition(), SkMakeSpan(argVals), result.asSpan());
Brian Osman54515b72021-01-07 14:38:08 -05001184 }
1185
1186 // Propagate new values of any 'out' params back to the original arguments
1187 const std::unique_ptr<Expression>* argIter = f.arguments().begin();
1188 size_t valIdx = 0;
1189 for (const Variable* p : decl.parameters()) {
John Stiles68f56062021-08-03 12:31:56 -04001190 nslots = p->type().slotCount();
Brian Osman54515b72021-01-07 14:38:08 -05001191 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1192 Value v(nslots);
1193 for (size_t i = 0; i < nslots; ++i) {
1194 v[i] = argVals[valIdx + i];
1195 }
1196 const std::unique_ptr<Expression>& arg = *argIter;
1197 this->writeStore(*arg, v);
1198 }
1199 valIdx += nslots;
1200 argIter++;
1201 }
1202
1203 return result;
Brian Osman0a442b72020-12-02 11:12:51 -05001204}
1205
Brian Osmandd50b0c2021-01-11 17:04:29 -05001206Value SkVMGenerator::writeExternalFunctionCall(const ExternalFunctionCall& c) {
1207 // Evaluate all arguments, gather the results into a contiguous list of F32
1208 std::vector<skvm::F32> args;
1209 for (const auto& arg : c.arguments()) {
1210 Value v = this->writeExpression(*arg);
1211 for (size_t i = 0; i < v.slots(); ++i) {
1212 args.push_back(f32(v[i]));
1213 }
1214 }
1215
1216 // Create storage for the return value
John Stiles47b087e2021-04-06 13:19:35 -04001217 size_t nslots = c.type().slotCount();
Brian Osmandd50b0c2021-01-11 17:04:29 -05001218 std::vector<skvm::F32> result(nslots, fBuilder->splat(0.0f));
1219
1220 c.function().call(fBuilder, args.data(), result.data(), this->mask());
1221
1222 // Convert from 'vector of F32' to Value
1223 Value resultVal(nslots);
1224 for (size_t i = 0; i < nslots; ++i) {
1225 resultVal[i] = result[i];
1226 }
1227
1228 return resultVal;
1229}
1230
Brian Osman0a442b72020-12-02 11:12:51 -05001231Value SkVMGenerator::writePrefixExpression(const PrefixExpression& p) {
1232 Value val = this->writeExpression(*p.operand());
1233
John Stiles45990502021-02-16 10:55:27 -05001234 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001235 case Token::Kind::TK_PLUSPLUS:
1236 case Token::Kind::TK_MINUSMINUS: {
John Stiles45990502021-02-16 10:55:27 -05001237 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001238
1239 switch (base_number_kind(p.type())) {
1240 case Type::NumberKind::kFloat:
1241 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1242 break;
1243 case Type::NumberKind::kSigned:
1244 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1245 break;
1246 default:
1247 SkASSERT(false);
1248 return {};
1249 }
1250 return this->writeStore(*p.operand(), val);
1251 }
1252 case Token::Kind::TK_MINUS: {
1253 switch (base_number_kind(p.type())) {
1254 case Type::NumberKind::kFloat:
1255 return this->unary(val, [](skvm::F32 x) { return -x; });
1256 case Type::NumberKind::kSigned:
1257 return this->unary(val, [](skvm::I32 x) { return -x; });
1258 default:
1259 SkASSERT(false);
1260 return {};
1261 }
1262 }
1263 case Token::Kind::TK_LOGICALNOT:
1264 case Token::Kind::TK_BITWISENOT:
1265 return this->unary(val, [](skvm::I32 x) { return ~x; });
1266 default:
1267 SkASSERT(false);
1268 return {};
1269 }
1270}
1271
1272Value SkVMGenerator::writePostfixExpression(const PostfixExpression& p) {
John Stiles45990502021-02-16 10:55:27 -05001273 switch (p.getOperator().kind()) {
Brian Osman0a442b72020-12-02 11:12:51 -05001274 case Token::Kind::TK_PLUSPLUS:
1275 case Token::Kind::TK_MINUSMINUS: {
1276 Value old = this->writeExpression(*p.operand()),
1277 val = old;
1278 SkASSERT(val.slots() == 1);
John Stiles45990502021-02-16 10:55:27 -05001279 bool incr = p.getOperator().kind() == Token::Kind::TK_PLUSPLUS;
Brian Osman0a442b72020-12-02 11:12:51 -05001280
1281 switch (base_number_kind(p.type())) {
1282 case Type::NumberKind::kFloat:
1283 val = f32(val) + fBuilder->splat(incr ? 1.0f : -1.0f);
1284 break;
1285 case Type::NumberKind::kSigned:
1286 val = i32(val) + fBuilder->splat(incr ? 1 : -1);
1287 break;
1288 default:
1289 SkASSERT(false);
1290 return {};
1291 }
1292 this->writeStore(*p.operand(), val);
1293 return old;
1294 }
1295 default:
1296 SkASSERT(false);
1297 return {};
1298 }
1299}
1300
1301Value SkVMGenerator::writeSwizzle(const Swizzle& s) {
1302 Value base = this->writeExpression(*s.base());
1303 Value swizzled(s.components().size());
1304 for (size_t i = 0; i < s.components().size(); ++i) {
1305 swizzled[i] = base[s.components()[i]];
1306 }
1307 return swizzled;
1308}
1309
1310Value SkVMGenerator::writeTernaryExpression(const TernaryExpression& t) {
1311 skvm::I32 test = i32(this->writeExpression(*t.test()));
1312 Value ifTrue, ifFalse;
1313
1314 {
Brian Osman9333c872021-01-13 15:06:17 -05001315 ScopedCondition m(this, test);
Brian Osman0a442b72020-12-02 11:12:51 -05001316 ifTrue = this->writeExpression(*t.ifTrue());
1317 }
1318 {
Brian Osman9333c872021-01-13 15:06:17 -05001319 ScopedCondition m(this, ~test);
Brian Osman0a442b72020-12-02 11:12:51 -05001320 ifFalse = this->writeExpression(*t.ifFalse());
1321 }
1322
1323 size_t nslots = ifTrue.slots();
1324 SkASSERT(nslots == ifFalse.slots());
1325
1326 Value result(nslots);
1327 for (size_t i = 0; i < nslots; ++i) {
1328 result[i] = skvm::select(test, i32(ifTrue[i]), i32(ifFalse[i]));
1329 }
1330 return result;
1331}
1332
1333Value SkVMGenerator::writeExpression(const Expression& e) {
1334 switch (e.kind()) {
1335 case Expression::Kind::kBinary:
1336 return this->writeBinaryExpression(e.as<BinaryExpression>());
1337 case Expression::Kind::kBoolLiteral:
1338 return fBuilder->splat(e.as<BoolLiteral>().value() ? ~0 : 0);
John Stiles7384b372021-04-01 13:48:15 -04001339 case Expression::Kind::kConstructorArray:
John Stiles8cad6372021-04-07 12:31:13 -04001340 case Expression::Kind::kConstructorCompound:
John Stilesd47330f2021-04-08 23:25:52 -04001341 case Expression::Kind::kConstructorStruct:
John Stilesd986f472021-04-06 15:54:43 -04001342 return this->writeAggregationConstructor(e.asAnyConstructor());
John Stilese3ae9682021-08-05 10:35:01 -04001343 case Expression::Kind::kConstructorArrayCast:
1344 return this->writeExpression(*e.as<ConstructorArrayCast>().argument());
John Stilese1182782021-03-30 22:09:37 -04001345 case Expression::Kind::kConstructorDiagonalMatrix:
1346 return this->writeConstructorDiagonalMatrix(e.as<ConstructorDiagonalMatrix>());
John Stiles5abb9e12021-04-06 13:47:19 -04001347 case Expression::Kind::kConstructorMatrixResize:
1348 return this->writeConstructorMatrixResize(e.as<ConstructorMatrixResize>());
John Stilesfd7252f2021-04-04 22:24:40 -04001349 case Expression::Kind::kConstructorScalarCast:
John Stiles8cad6372021-04-07 12:31:13 -04001350 case Expression::Kind::kConstructorCompoundCast:
John Stilesb14a8192021-04-05 11:40:46 -04001351 return this->writeConstructorCast(e.asAnyConstructor());
John Stiles2938eea2021-04-01 18:58:25 -04001352 case Expression::Kind::kConstructorSplat:
1353 return this->writeConstructorSplat(e.as<ConstructorSplat>());
Brian Osman0a442b72020-12-02 11:12:51 -05001354 case Expression::Kind::kFieldAccess:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001355 return this->writeFieldAccess(e.as<FieldAccess>());
Brian Osman0a442b72020-12-02 11:12:51 -05001356 case Expression::Kind::kIndex:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001357 return this->writeIndexExpression(e.as<IndexExpression>());
Brian Osman0a442b72020-12-02 11:12:51 -05001358 case Expression::Kind::kVariableReference:
Brian Osmanfa71ffa2021-01-26 14:05:31 -05001359 return this->writeVariableExpression(e.as<VariableReference>());
Brian Osman0a442b72020-12-02 11:12:51 -05001360 case Expression::Kind::kFloatLiteral:
1361 return fBuilder->splat(e.as<FloatLiteral>().value());
1362 case Expression::Kind::kFunctionCall:
1363 return this->writeFunctionCall(e.as<FunctionCall>());
Brian Osmandd50b0c2021-01-11 17:04:29 -05001364 case Expression::Kind::kExternalFunctionCall:
1365 return this->writeExternalFunctionCall(e.as<ExternalFunctionCall>());
Brian Osman0a442b72020-12-02 11:12:51 -05001366 case Expression::Kind::kIntLiteral:
1367 return fBuilder->splat(static_cast<int>(e.as<IntLiteral>().value()));
Brian Osman0a442b72020-12-02 11:12:51 -05001368 case Expression::Kind::kPrefix:
1369 return this->writePrefixExpression(e.as<PrefixExpression>());
1370 case Expression::Kind::kPostfix:
1371 return this->writePostfixExpression(e.as<PostfixExpression>());
1372 case Expression::Kind::kSwizzle:
1373 return this->writeSwizzle(e.as<Swizzle>());
1374 case Expression::Kind::kTernary:
1375 return this->writeTernaryExpression(e.as<TernaryExpression>());
Brian Osmanbe0b3b72021-01-06 14:27:35 -05001376 case Expression::Kind::kExternalFunctionReference:
Brian Osman0a442b72020-12-02 11:12:51 -05001377 default:
1378 SkDEBUGFAIL("Unsupported expression");
1379 return {};
1380 }
1381}
1382
1383Value SkVMGenerator::writeStore(const Expression& lhs, const Value& rhs) {
John Stiles47b087e2021-04-06 13:19:35 -04001384 SkASSERTF(rhs.slots() == lhs.type().slotCount(),
John Stiles7bf79992021-06-25 11:05:20 -04001385 "lhs=%s (%s)\nrhs=%zu slot",
John Stiles94e72b92021-01-30 11:06:18 -05001386 lhs.type().description().c_str(), lhs.description().c_str(), rhs.slots());
Brian Osman0a442b72020-12-02 11:12:51 -05001387
Brian Osman21f57072021-01-25 13:51:57 -05001388 // We need to figure out the collection of slots that we're storing into. The l-value (lhs)
1389 // is always a VariableReference, possibly wrapped by one or more Swizzle, FieldAccess, or
1390 // IndexExpressions. The underlying VariableReference has a range of slots for its storage,
1391 // and each expression wrapped around that selects a sub-set of those slots (Field/Index),
1392 // or rearranges them (Swizzle).
1393 SkSTArray<4, size_t, true> slots;
1394 slots.resize(rhs.slots());
1395
1396 // Start with the identity slot map - this basically says that the values from rhs belong in
1397 // slots [0, 1, 2 ... N] of the lhs.
1398 for (size_t i = 0; i < slots.size(); ++i) {
1399 slots[i] = i;
1400 }
1401
1402 // Now, as we peel off each outer expression, adjust 'slots' to be the locations relative to
1403 // the next (inner) expression:
1404 const Expression* expr = &lhs;
1405 while (!expr->is<VariableReference>()) {
1406 switch (expr->kind()) {
1407 case Expression::Kind::kFieldAccess: {
1408 const FieldAccess& fld = expr->as<FieldAccess>();
1409 size_t offset = this->fieldSlotOffset(fld);
1410 for (size_t& s : slots) {
1411 s += offset;
1412 }
1413 expr = fld.base().get();
1414 } break;
1415 case Expression::Kind::kIndex: {
1416 const IndexExpression& idx = expr->as<IndexExpression>();
1417 size_t offset = this->indexSlotOffset(idx);
1418 for (size_t& s : slots) {
1419 s += offset;
1420 }
1421 expr = idx.base().get();
1422 } break;
1423 case Expression::Kind::kSwizzle: {
1424 const Swizzle& swz = expr->as<Swizzle>();
1425 for (size_t& s : slots) {
1426 s = swz.components()[s];
1427 }
1428 expr = swz.base().get();
1429 } break;
1430 default:
1431 // No other kinds of expressions are valid in lvalues. (see Analysis::IsAssignable)
1432 SkDEBUGFAIL("Invalid expression type");
1433 return {};
1434 }
1435 }
1436
1437 // When we get here, 'slots' are all relative to the first slot holding 'var's storage
1438 const Variable& var = *expr->as<VariableReference>().variable();
1439 size_t varSlot = this->getSlot(var);
Brian Osman0a442b72020-12-02 11:12:51 -05001440 skvm::I32 mask = this->mask();
1441 for (size_t i = rhs.slots(); i --> 0;) {
John Stiles47b087e2021-04-06 13:19:35 -04001442 SkASSERT(slots[i] < var.type().slotCount());
Brian Osman21f57072021-01-25 13:51:57 -05001443 skvm::F32 curr = f32(fSlots[varSlot + slots[i]]),
Brian Osman0a442b72020-12-02 11:12:51 -05001444 next = f32(rhs[i]);
Brian Osman21f57072021-01-25 13:51:57 -05001445 fSlots[varSlot + slots[i]] = select(mask, next, curr).id;
Brian Osman0a442b72020-12-02 11:12:51 -05001446 }
1447 return rhs;
1448}
1449
1450void SkVMGenerator::writeBlock(const Block& b) {
1451 for (const std::unique_ptr<Statement>& stmt : b.children()) {
1452 this->writeStatement(*stmt);
1453 }
1454}
1455
Brian Osman9333c872021-01-13 15:06:17 -05001456void SkVMGenerator::writeBreakStatement() {
1457 // Any active lanes stop executing for the duration of the current loop
1458 fLoopMask &= ~this->mask();
1459}
1460
1461void SkVMGenerator::writeContinueStatement() {
1462 // Any active lanes stop executing for the current iteration.
1463 // Remember them in fContinueMask, to be re-enabled later.
1464 skvm::I32 mask = this->mask();
1465 fLoopMask &= ~mask;
1466 fContinueMask |= mask;
1467}
1468
1469void SkVMGenerator::writeForStatement(const ForStatement& f) {
1470 // We require that all loops be ES2-compliant (unrollable), and actually unroll them here
1471 Analysis::UnrollableLoopInfo loop;
John Stiles232b4ce2021-03-01 22:14:22 -05001472 SkAssertResult(Analysis::ForLoopIsValidForES2(f.fOffset, f.initializer().get(), f.test().get(),
1473 f.next().get(), f.statement().get(), &loop,
1474 /*errors=*/nullptr));
John Stiles47b087e2021-04-06 13:19:35 -04001475 SkASSERT(loop.fIndex->type().slotCount() == 1);
Brian Osman9333c872021-01-13 15:06:17 -05001476
Brian Osman21f57072021-01-25 13:51:57 -05001477 size_t indexSlot = this->getSlot(*loop.fIndex);
Brian Osman9333c872021-01-13 15:06:17 -05001478 double val = loop.fStart;
1479
1480 skvm::I32 oldLoopMask = fLoopMask,
1481 oldContinueMask = fContinueMask;
1482
1483 for (int i = 0; i < loop.fCount; ++i) {
Brian Osman21f57072021-01-25 13:51:57 -05001484 fSlots[indexSlot] = loop.fIndex->type().isInteger()
1485 ? fBuilder->splat(static_cast<int>(val)).id
1486 : fBuilder->splat(static_cast<float>(val)).id;
Brian Osman9333c872021-01-13 15:06:17 -05001487
1488 fContinueMask = fBuilder->splat(0);
1489 this->writeStatement(*f.statement());
1490 fLoopMask |= fContinueMask;
1491
1492 val += loop.fDelta;
1493 }
1494
1495 fLoopMask = oldLoopMask;
1496 fContinueMask = oldContinueMask;
1497}
1498
Brian Osman0a442b72020-12-02 11:12:51 -05001499void SkVMGenerator::writeIfStatement(const IfStatement& i) {
1500 Value test = this->writeExpression(*i.test());
1501 {
Brian Osman9333c872021-01-13 15:06:17 -05001502 ScopedCondition ifTrue(this, i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001503 this->writeStatement(*i.ifTrue());
1504 }
1505 if (i.ifFalse()) {
Brian Osman9333c872021-01-13 15:06:17 -05001506 ScopedCondition ifFalse(this, ~i32(test));
Brian Osman0a442b72020-12-02 11:12:51 -05001507 this->writeStatement(*i.ifFalse());
1508 }
1509}
1510
1511void SkVMGenerator::writeReturnStatement(const ReturnStatement& r) {
Brian Osman54515b72021-01-07 14:38:08 -05001512 skvm::I32 returnsHere = this->mask();
Brian Osman0a442b72020-12-02 11:12:51 -05001513
Brian Osman54515b72021-01-07 14:38:08 -05001514 if (r.expression()) {
1515 Value val = this->writeExpression(*r.expression());
Brian Osman0a442b72020-12-02 11:12:51 -05001516
Brian Osman54515b72021-01-07 14:38:08 -05001517 int i = 0;
1518 for (skvm::Val& slot : currentFunction().fReturnValue) {
1519 slot = select(returnsHere, f32(val[i]), f32(slot)).id;
1520 i++;
1521 }
Brian Osman0a442b72020-12-02 11:12:51 -05001522 }
1523
Brian Osman54515b72021-01-07 14:38:08 -05001524 currentFunction().fReturned |= returnsHere;
Brian Osman0a442b72020-12-02 11:12:51 -05001525}
1526
1527void SkVMGenerator::writeVarDeclaration(const VarDeclaration& decl) {
Brian Osman21f57072021-01-25 13:51:57 -05001528 size_t slot = this->getSlot(decl.var()),
John Stiles47b087e2021-04-06 13:19:35 -04001529 nslots = decl.var().type().slotCount();
Brian Osman0a442b72020-12-02 11:12:51 -05001530
1531 Value val = decl.value() ? this->writeExpression(*decl.value()) : Value{};
1532 for (size_t i = 0; i < nslots; ++i) {
1533 fSlots[slot + i] = val ? val[i] : fBuilder->splat(0.0f).id;
1534 }
1535}
1536
1537void SkVMGenerator::writeStatement(const Statement& s) {
1538 switch (s.kind()) {
1539 case Statement::Kind::kBlock:
1540 this->writeBlock(s.as<Block>());
1541 break;
Brian Osman9333c872021-01-13 15:06:17 -05001542 case Statement::Kind::kBreak:
1543 this->writeBreakStatement();
1544 break;
1545 case Statement::Kind::kContinue:
1546 this->writeContinueStatement();
1547 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001548 case Statement::Kind::kExpression:
1549 this->writeExpression(*s.as<ExpressionStatement>().expression());
1550 break;
Brian Osman9333c872021-01-13 15:06:17 -05001551 case Statement::Kind::kFor:
1552 this->writeForStatement(s.as<ForStatement>());
1553 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001554 case Statement::Kind::kIf:
1555 this->writeIfStatement(s.as<IfStatement>());
1556 break;
1557 case Statement::Kind::kReturn:
1558 this->writeReturnStatement(s.as<ReturnStatement>());
1559 break;
1560 case Statement::Kind::kVarDeclaration:
1561 this->writeVarDeclaration(s.as<VarDeclaration>());
1562 break;
Brian Osman0a442b72020-12-02 11:12:51 -05001563 case Statement::Kind::kDiscard:
1564 case Statement::Kind::kDo:
Brian Osman0a442b72020-12-02 11:12:51 -05001565 case Statement::Kind::kSwitch:
Brian Osman57e353f2021-01-07 15:55:20 -05001566 SkDEBUGFAIL("Unsupported control flow");
Brian Osman0a442b72020-12-02 11:12:51 -05001567 break;
1568 case Statement::Kind::kInlineMarker:
1569 case Statement::Kind::kNop:
1570 break;
1571 default:
1572 SkASSERT(false);
1573 }
1574}
1575
1576skvm::Color ProgramToSkVM(const Program& program,
1577 const FunctionDefinition& function,
1578 skvm::Builder* builder,
1579 SkSpan<skvm::Val> uniforms,
1580 skvm::Coord device,
1581 skvm::Coord local,
Brian Osman577c6062021-04-12 17:17:19 -04001582 skvm::Color inputColor,
John Stiles50d0d092021-06-09 17:24:31 -04001583 skvm::Color destColor,
John Stiles137482f2021-07-23 10:38:57 -04001584 SampleShaderFn sampleShader,
John Stiles2955c262021-07-23 15:51:05 -04001585 SampleColorFilterFn sampleColorFilter,
1586 SampleBlenderFn sampleBlender) {
Mike Kleinaebcf732021-01-14 10:15:00 -06001587 skvm::Val zero = builder->splat(0.0f).id;
1588 skvm::Val result[4] = {zero,zero,zero,zero};
Brian Osman577c6062021-04-12 17:17:19 -04001589
John Stilesf7f36ae2021-06-08 14:06:22 -04001590 skvm::Val args[8]; // At most 8 arguments (half4 srcColor, half4 dstColor)
Brian Osman577c6062021-04-12 17:17:19 -04001591 size_t argSlots = 0;
Brian Osman0a442b72020-12-02 11:12:51 -05001592 for (const SkSL::Variable* param : function.declaration().parameters()) {
Brian Osman577c6062021-04-12 17:17:19 -04001593 switch (param->modifiers().fLayout.fBuiltin) {
1594 case SK_MAIN_COORDS_BUILTIN:
1595 SkASSERT(param->type().slotCount() == 2);
John Stilesf7f36ae2021-06-08 14:06:22 -04001596 SkASSERT((argSlots + 2) <= SK_ARRAY_COUNT(args));
Brian Osman577c6062021-04-12 17:17:19 -04001597 args[argSlots++] = local.x.id;
1598 args[argSlots++] = local.y.id;
1599 break;
1600 case SK_INPUT_COLOR_BUILTIN:
1601 SkASSERT(param->type().slotCount() == 4);
John Stilesf7f36ae2021-06-08 14:06:22 -04001602 SkASSERT((argSlots + 4) <= SK_ARRAY_COUNT(args));
Brian Osman577c6062021-04-12 17:17:19 -04001603 args[argSlots++] = inputColor.r.id;
1604 args[argSlots++] = inputColor.g.id;
1605 args[argSlots++] = inputColor.b.id;
1606 args[argSlots++] = inputColor.a.id;
1607 break;
John Stiles50d0d092021-06-09 17:24:31 -04001608 case SK_DEST_COLOR_BUILTIN:
1609 SkASSERT(param->type().slotCount() == 4);
1610 SkASSERT((argSlots + 4) <= SK_ARRAY_COUNT(args));
1611 args[argSlots++] = destColor.r.id;
1612 args[argSlots++] = destColor.g.id;
1613 args[argSlots++] = destColor.b.id;
1614 args[argSlots++] = destColor.a.id;
1615 break;
Brian Osman577c6062021-04-12 17:17:19 -04001616 default:
1617 SkDEBUGFAIL("Invalid parameter to main()");
1618 return {};
1619 }
Brian Osman0a442b72020-12-02 11:12:51 -05001620 }
Brian Osman577c6062021-04-12 17:17:19 -04001621 SkASSERT(argSlots <= SK_ARRAY_COUNT(args));
Brian Osman0a442b72020-12-02 11:12:51 -05001622
John Stilesd9a56b92021-07-23 15:50:39 -04001623 SkVMGenerator generator(program, builder, uniforms, device, local, std::move(sampleShader),
John Stiles2955c262021-07-23 15:51:05 -04001624 std::move(sampleColorFilter), std::move(sampleBlender));
Brian Osmanae87bf12021-05-11 13:36:10 -04001625 generator.writeFunction(function, {args, argSlots}, SkMakeSpan(result));
Brian Osman0a442b72020-12-02 11:12:51 -05001626
Brian Osman57e353f2021-01-07 15:55:20 -05001627 return skvm::Color{{builder, result[0]},
1628 {builder, result[1]},
1629 {builder, result[2]},
1630 {builder, result[3]}};
Brian Osman0a442b72020-12-02 11:12:51 -05001631}
1632
Brian Osmanf4a77732020-12-28 09:03:00 -05001633bool ProgramToSkVM(const Program& program,
1634 const FunctionDefinition& function,
1635 skvm::Builder* b,
Brian Osmanc92df392021-01-11 13:16:28 -05001636 SkSpan<skvm::Val> uniforms,
Brian Osmanf4a77732020-12-28 09:03:00 -05001637 SkVMSignature* outSignature) {
Brian Osmanf4a77732020-12-28 09:03:00 -05001638 SkVMSignature ignored,
1639 *signature = outSignature ? outSignature : &ignored;
1640
Mike Klein00e43df2021-01-08 13:45:42 -06001641 std::vector<skvm::Ptr> argPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001642 std::vector<skvm::Val> argVals;
1643
1644 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001645 size_t slots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001646 signature->fParameterSlots += slots;
1647 for (size_t i = 0; i < slots; ++i) {
1648 argPtrs.push_back(b->varying<float>());
1649 argVals.push_back(b->loadF(argPtrs.back()).id);
1650 }
1651 }
1652
Mike Klein00e43df2021-01-08 13:45:42 -06001653 std::vector<skvm::Ptr> returnPtrs;
Brian Osmanf4a77732020-12-28 09:03:00 -05001654 std::vector<skvm::Val> returnVals;
1655
John Stiles47b087e2021-04-06 13:19:35 -04001656 signature->fReturnSlots = function.declaration().returnType().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001657 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1658 returnPtrs.push_back(b->varying<float>());
1659 returnVals.push_back(b->splat(0.0f).id);
1660 }
1661
Brian Osmanc9125aa2021-04-21 09:57:19 -04001662 skvm::F32 zero = b->splat(0.0f);
1663 skvm::Coord zeroCoord = {zero, zero};
Brian Osmanc92df392021-01-11 13:16:28 -05001664 SkVMGenerator generator(program, b, uniforms, /*device=*/zeroCoord, /*local=*/zeroCoord,
John Stiles2955c262021-07-23 15:51:05 -04001665 /*sampleShader=*/nullptr, /*sampleColorFilter=*/nullptr,
1666 /*sampleBlender=*/nullptr);
Brian Osmanae87bf12021-05-11 13:36:10 -04001667 generator.writeFunction(function, SkMakeSpan(argVals), SkMakeSpan(returnVals));
Brian Osmanf4a77732020-12-28 09:03:00 -05001668
1669 // generateCode has updated the contents of 'argVals' for any 'out' or 'inout' parameters.
1670 // Propagate those changes back to our varying buffers:
1671 size_t argIdx = 0;
1672 for (const Variable* p : function.declaration().parameters()) {
John Stiles47b087e2021-04-06 13:19:35 -04001673 size_t nslots = p->type().slotCount();
Brian Osmanf4a77732020-12-28 09:03:00 -05001674 if (p->modifiers().fFlags & Modifiers::kOut_Flag) {
1675 for (size_t i = 0; i < nslots; ++i) {
1676 b->storeF(argPtrs[argIdx + i], skvm::F32{b, argVals[argIdx + i]});
1677 }
1678 }
1679 argIdx += nslots;
1680 }
1681
1682 // It's also updated the contents of 'returnVals' with the return value of the entry point.
1683 // Store that as well:
1684 for (size_t i = 0; i < signature->fReturnSlots; ++i) {
1685 b->storeF(returnPtrs[i], skvm::F32{b, returnVals[i]});
1686 }
1687
1688 return true;
1689}
1690
Brian Osman5933d4c2021-01-05 13:02:20 -05001691const FunctionDefinition* Program_GetFunction(const Program& program, const char* function) {
1692 for (const ProgramElement* e : program.elements()) {
1693 if (e->is<FunctionDefinition>() &&
1694 e->as<FunctionDefinition>().declaration().name() == function) {
1695 return &e->as<FunctionDefinition>();
1696 }
1697 }
1698 return nullptr;
1699}
1700
Brian Osmane89d8ea2021-01-20 14:01:30 -05001701static void gather_uniforms(UniformInfo* info, const Type& type, const String& name) {
1702 switch (type.typeKind()) {
1703 case Type::TypeKind::kStruct:
1704 for (const auto& f : type.fields()) {
1705 gather_uniforms(info, *f.fType, name + "." + f.fName);
1706 }
1707 break;
1708 case Type::TypeKind::kArray:
1709 for (int i = 0; i < type.columns(); ++i) {
1710 gather_uniforms(info, type.componentType(),
1711 String::printf("%s[%d]", name.c_str(), i));
1712 }
1713 break;
1714 case Type::TypeKind::kScalar:
1715 case Type::TypeKind::kVector:
1716 case Type::TypeKind::kMatrix:
1717 info->fUniforms.push_back({name, base_number_kind(type), type.rows(), type.columns(),
1718 info->fUniformSlotCount});
1719 info->fUniformSlotCount += type.columns() * type.rows();
1720 break;
1721 default:
1722 break;
1723 }
1724}
1725
1726std::unique_ptr<UniformInfo> Program_GetUniformInfo(const Program& program) {
1727 auto info = std::make_unique<UniformInfo>();
1728 for (const ProgramElement* e : program.elements()) {
1729 if (!e->is<GlobalVarDeclaration>()) {
1730 continue;
1731 }
1732 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1733 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
1734 if (var.modifiers().fFlags & Modifiers::kUniform_Flag) {
Ethan Nicholasd2e09602021-06-10 11:21:59 -04001735 gather_uniforms(info.get(), var.type(), String(var.name()));
Brian Osmane89d8ea2021-01-20 14:01:30 -05001736 }
1737 }
1738 return info;
1739}
1740
Brian Osman47726a12020-12-17 16:02:08 -05001741/*
1742 * Testing utility function that emits program's "main" with a minimal harness. Used to create
1743 * representative skvm op sequences for SkSL tests.
1744 */
1745bool testingOnly_ProgramToSkVMShader(const Program& program, skvm::Builder* builder) {
Brian Osman5933d4c2021-01-05 13:02:20 -05001746 const SkSL::FunctionDefinition* main = Program_GetFunction(program, "main");
1747 if (!main) {
1748 return false;
1749 }
1750
Brian Osman47726a12020-12-17 16:02:08 -05001751 size_t uniformSlots = 0;
1752 int childSlots = 0;
1753 for (const SkSL::ProgramElement* e : program.elements()) {
Brian Osman47726a12020-12-17 16:02:08 -05001754 if (e->is<GlobalVarDeclaration>()) {
1755 const GlobalVarDeclaration& decl = e->as<GlobalVarDeclaration>();
1756 const Variable& var = decl.declaration()->as<VarDeclaration>().var();
Brian Osman14d00962021-04-02 17:04:35 -04001757 if (var.type().isEffectChild()) {
Brian Osman47726a12020-12-17 16:02:08 -05001758 childSlots++;
1759 } else if (is_uniform(var)) {
John Stiles47b087e2021-04-06 13:19:35 -04001760 uniformSlots += var.type().slotCount();
Brian Osman47726a12020-12-17 16:02:08 -05001761 }
1762 }
1763 }
Brian Osman0a442b72020-12-02 11:12:51 -05001764
Mike Kleinae562bd2021-01-08 14:15:55 -06001765 skvm::Uniforms uniforms(builder->uniform(), 0);
Brian Osman47726a12020-12-17 16:02:08 -05001766
1767 auto new_uni = [&]() { return builder->uniformF(uniforms.pushF(0.0f)); };
1768
1769 // Assume identity CTM
1770 skvm::Coord device = {pun_to_F32(builder->index()), new_uni()};
1771 skvm::Coord local = device;
1772
1773 struct Child {
1774 skvm::Uniform addr;
1775 skvm::I32 rowBytesAsPixels;
1776 };
1777
1778 std::vector<Child> children;
1779 for (int i = 0; i < childSlots; ++i) {
1780 children.push_back({uniforms.pushPtr(nullptr), builder->uniform32(uniforms.push(0))});
1781 }
1782
John Stilesd9a56b92021-07-23 15:50:39 -04001783 auto sampleShader = [&](int i, skvm::Coord coord) {
Mike Klein447f3312021-02-08 09:46:59 -06001784 skvm::PixelFormat pixelFormat = skvm::SkColorType_to_PixelFormat(kRGBA_F32_SkColorType);
Brian Osman3f904db2021-01-28 13:24:31 -05001785 skvm::I32 index = trunc(coord.x);
1786 index += trunc(coord.y) * children[i].rowBytesAsPixels;
Brian Osman47726a12020-12-17 16:02:08 -05001787 return gather(pixelFormat, children[i].addr, index);
1788 };
1789
1790 std::vector<skvm::Val> uniformVals;
1791 for (size_t i = 0; i < uniformSlots; ++i) {
1792 uniformVals.push_back(new_uni().id);
1793 }
1794
Brian Osman577c6062021-04-12 17:17:19 -04001795 skvm::Color inColor = builder->uniformColor(SkColors::kWhite, &uniforms);
John Stiles50d0d092021-06-09 17:24:31 -04001796 skvm::Color destColor = builder->uniformColor(SkColors::kBlack, &uniforms);
Brian Osman577c6062021-04-12 17:17:19 -04001797
John Stiles50d0d092021-06-09 17:24:31 -04001798 skvm::Color result = SkSL::ProgramToSkVM(program, *main, builder, SkMakeSpan(uniformVals),
John Stiles137482f2021-07-23 10:38:57 -04001799 device, local, inColor, destColor, sampleShader,
John Stiles2955c262021-07-23 15:51:05 -04001800 /*sampleColorFilter=*/nullptr,
1801 /*sampleBlender=*/nullptr);
Brian Osman47726a12020-12-17 16:02:08 -05001802
1803 storeF(builder->varying<float>(), result.r);
1804 storeF(builder->varying<float>(), result.g);
1805 storeF(builder->varying<float>(), result.b);
1806 storeF(builder->varying<float>(), result.a);
1807
1808 return true;
1809
1810}
1811
1812} // namespace SkSL