Project

General

Profile

Download (26.6 KB) Statistics
| Branch: | Revision:

library / src / main / res / raw / main_vertex_shader.glsl @ 82ee855a

1 d333eb6b Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
2
// Copyright 2016 Leszek Koltunski                                                          //
3
//                                                                                          //
4
// This file is part of Distorted.                                                          //
5
//                                                                                          //
6
// Distorted is free software: you can redistribute it and/or modify                        //
7
// it under the terms of the GNU General Public License as published by                     //
8
// the Free Software Foundation, either version 2 of the License, or                        //
9
// (at your option) any later version.                                                      //
10
//                                                                                          //
11
// Distorted is distributed in the hope that it will be useful,                             //
12
// but WITHOUT ANY WARRANTY; without even the implied warranty of                           //
13
// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the                            //
14
// GNU General Public License for more details.                                             //
15
//                                                                                          //
16
// You should have received a copy of the GNU General Public License                        // 
17
// along with Distorted.  If not, see <http://www.gnu.org/licenses/>.                       //
18
//////////////////////////////////////////////////////////////////////////////////////////////
19
20 0318e7e3 Leszek Koltunski
uniform vec3 u_objD;                      // half of object width x half of object height X half the depth;
21 d333eb6b Leszek Koltunski
                                          // point (0,0,0) is the center of the object
22 6a06a912 Leszek Koltunski
23 d333eb6b Leszek Koltunski
uniform float u_Depth;                    // max absolute value of v.z ; beyond that the vertex would be culled by the near or far planes.
24
                                          // I read OpenGL ES has a built-in uniform variable gl_DepthRange.near = n, 
25
                                          // .far = f, .diff = f-n so maybe u_Depth is redundant
26
                                          // Update: this struct is only available in fragment shaders
27 6a06a912 Leszek Koltunski
                                
28 d333eb6b Leszek Koltunski
uniform mat4 u_MVPMatrix;                 // A constant representing the combined model/view/projection matrix.      		       
29
uniform mat4 u_MVMatrix;                  // A constant representing the combined model/view matrix.       		
30 6a06a912 Leszek Koltunski
		 
31 d333eb6b Leszek Koltunski
attribute vec3 a_Position;                // Per-vertex position information we will pass in.   				
32 2dacdeb2 Leszek Koltunski
attribute vec3 a_Normal;                  // Per-vertex normal information we will pass in.
33 d333eb6b Leszek Koltunski
attribute vec2 a_TexCoordinate;           // Per-vertex texture coordinate information we will pass in. 		
34 6a06a912 Leszek Koltunski
		  
35 d333eb6b Leszek Koltunski
varying vec3 v_Position;                  //      		
36 2dacdeb2 Leszek Koltunski
varying vec3 v_Normal;                    //
37 d333eb6b Leszek Koltunski
varying vec2 v_TexCoordinate;             //  		
38 6a06a912 Leszek Koltunski
39
uniform int vNumEffects;                  // total number of vertex effects
40
41
#if NUM_VERTEX>0
42
uniform int vType[NUM_VERTEX];            // their types.
43 4fde55a0 Leszek Koltunski
uniform vec4 vUniforms[3*NUM_VERTEX];     // i-th effect is 3 consecutive vec4's: [3*i], [3*i+1], [3*i+2].
44
                                          // The first vec4 is the Interpolated values,
45
                                          // next is half cache half Center, the third -  the Region.
46 6a06a912 Leszek Koltunski
#endif
47
48
#if NUM_VERTEX>0
49 341c803d Leszek Koltunski
50
//////////////////////////////////////////////////////////////////////////////////////////////
51
// HELPER FUNCTIONS
52
//////////////////////////////////////////////////////////////////////////////////////////////
53 9420f2fe Leszek Koltunski
// The trick below is the if-less version of the
54 341c803d Leszek Koltunski
//
55
// t = dx<0.0 ? (u_objD.x-v.x) / (u_objD.x-ux) : (u_objD.x+v.x) / (u_objD.x+ux);
56
// h = dy<0.0 ? (u_objD.y-v.y) / (u_objD.y-uy) : (u_objD.y+v.y) / (u_objD.y+uy);
57
// d = min(t,h);
58
//
59
// float d = min(-ps.x/(sign(ps.x)*u_objD.x+p.x),-ps.y/(sign(ps.y)*u_objD.y+p.y))+1.0;
60
//
61
// We still have to avoid division by 0 when p.x = +- u_objD.x or p.y = +- u_objD.y (i.e on the edge of the Object)
62
// We do that by first multiplying the above 'float d' with sign(denominator1*denominator2)^2.
63
//
64
//////////////////////////////////////////////////////////////////////////////////////////////
65
// return degree of the point as defined by the bitmap rectangle
66
67
float degree_bitmap(in vec2 S, in vec2 PS)
68
  {
69
  vec2 A = sign(PS)*u_objD.xy + S;
70
71 369ee56a Leszek Koltunski
  vec2 signA = sign(A);                           //
72
  vec2 signA_SQ = signA*signA;                    // div = PS/A if A!=0, 0 otherwise.
73 20af7b69 Leszek Koltunski
  vec2 div = signA_SQ*PS/(A-(vec2(1,1)-signA_SQ));//
74 369ee56a Leszek Koltunski
75
  return 1.0-max(div.x,div.y);
76 341c803d Leszek Koltunski
  }
77
78
//////////////////////////////////////////////////////////////////////////////////////////////
79 9420f2fe Leszek Koltunski
// Return degree of the point as defined by the Region. Currently only supports circular regions.
80
//
81 73af5285 Leszek Koltunski
// Let us first introduce some notation.
82 9420f2fe Leszek Koltunski
// Let 'PS' be the vector from point P (the current vertex) to point S (the center of the effect).
83
// Let region.xy be the vector from point S to point O (the center point of the region circle)
84
// Let region.z be the radius of the region circle.
85 73af5285 Leszek Koltunski
// (This all should work regardless if S is inside or outside of the circle).
86
//
87
// Then, the degree of a point with respect to a given (circular!) Region is defined by:
88 9420f2fe Leszek Koltunski
//
89
// If P is outside the circle, return 0.
90 73af5285 Leszek Koltunski
// Otherwise, let X be the point where the halfline SP meets the region circle - then return |PX|/||SX|,
91 9420f2fe Leszek Koltunski
// aka the 'degree' of point P.
92
//
93 ff8ad0a7 Leszek Koltunski
// We solve the triangle OPX.
94 9420f2fe Leszek Koltunski
// We know the lengths |PO|, |OX| and the angle OPX, because cos(OPX) = cos(180-OPS) = -cos(OPS) = -PS*PO/(|PS|*|PO|)
95
// then from the law of cosines PX^2 + PO^2 - 2*PX*PO*cos(OPX) = OX^2 so PX = -a + sqrt(a^2 + OX^2 - PO^2)
96
// where a = PS*PO/|PS| but we are really looking for d = |PX|/(|PX|+|PS|) = 1/(1+ (|PS|/|PX|) ) and
97
// |PX|/|PS| = -b + sqrt(b^2 + (OX^2-PO^2)/PS^2) where b=PS*PO/|PS|^2 which can be computed with only one sqrt.
98 341c803d Leszek Koltunski
99 4fde55a0 Leszek Koltunski
float degree_region(in vec4 region, in vec2 PS)
100 341c803d Leszek Koltunski
  {
101
  vec2 PO  = PS + region.xy;
102
  float D = region.z*region.z-dot(PO,PO);      // D = |OX|^2 - |PO|^2
103 9420f2fe Leszek Koltunski
104
  if( D<=0.0 ) return 0.0;
105
106 341c803d Leszek Koltunski
  float ps_sq = dot(PS,PS);
107 20af7b69 Leszek Koltunski
  float one_over_ps_sq = 1.0/(ps_sq-(sign(ps_sq)-1.0));  // return 1.0 if ps_sq = 0.0
108
                                                         // Important: if we want to write
109
                                                         // b = 1/a if a!=0, b=1 otherwise
110
                                                         // we need to write that as
111
                                                         // b = 1 / ( a-(sign(a)-1) )
112
                                                         // [ and NOT 1 / ( a + 1 - sign(a) ) ]
113
                                                         // because the latter, if 0<a<2^-24,
114
                                                         // will suffer from round-off error and in this case
115
                                                         // a + 1.0 = 1.0 !! so 1 / (a+1-sign(a)) = 1/0 !
116 7c227ed2 Leszek Koltunski
  float DOT  = dot(PS,PO)*one_over_ps_sq;
117 341c803d Leszek Koltunski
118 9420f2fe Leszek Koltunski
  return 1.0 / (1.0 + 1.0/(sqrt(DOT*DOT+D*one_over_ps_sq)-DOT));
119 341c803d Leszek Koltunski
  }
120
121
//////////////////////////////////////////////////////////////////////////////////////////////
122
// return min(degree_bitmap,degree_region). Just like degree_region, currently only supports circles.
123
124 4fde55a0 Leszek Koltunski
float degree(in vec4 region, in vec2 S, in vec2 PS)
125 341c803d Leszek Koltunski
  {
126
  vec2 PO  = PS + region.xy;
127
  float D = region.z*region.z-dot(PO,PO);      // D = |OX|^2 - |PO|^2
128 9420f2fe Leszek Koltunski
129
  if( D<=0.0 ) return 0.0;
130
131 341c803d Leszek Koltunski
  vec2 A = sign(PS)*u_objD.xy + S;
132 369ee56a Leszek Koltunski
  vec2 signA = sign(A);
133
  vec2 signA_SQ = signA*signA;
134 20af7b69 Leszek Koltunski
  vec2 div = signA_SQ*PS/(A-(vec2(1,1)-signA_SQ));
135 369ee56a Leszek Koltunski
  float E = 1.0-max(div.x,div.y);
136
137 341c803d Leszek Koltunski
  float ps_sq = dot(PS,PS);
138 20af7b69 Leszek Koltunski
  float one_over_ps_sq = 1.0/(ps_sq-(sign(ps_sq)-1.0));  // return 1.0 if ps_sq = 0.0
139 7c227ed2 Leszek Koltunski
  float DOT  = dot(PS,PO)*one_over_ps_sq;
140 341c803d Leszek Koltunski
141 9420f2fe Leszek Koltunski
  return min(1.0/(1.0 + 1.0/(sqrt(DOT*DOT+D*one_over_ps_sq)-DOT)),E);
142 341c803d Leszek Koltunski
  }
143
144
//////////////////////////////////////////////////////////////////////////////////////////////
145
// Clamp v.z to (-u_Depth,u_Depth) with the following function:
146
// define h to be, say, 0.7; let H=u_Depth
147
//      if v.z < -hH then v.z = (-(1-h)^2 * H^2)/(v.z+(2h-1)H) -H   (function satisfying f(-hH)=-hH, f'(-hH)=1, lim f(x) = -H)
148
// else if v.z >  hH then v.z = (-(1-h)^2 * H^2)/(v.z-(2h-1)H) +H   (function satisfying f(+hH)=+hH, f'(+hH)=1, lim f(x) = +H)
149
// else v.z = v.z
150
151 291705f6 Leszek Koltunski
void restrictZ(inout float v)
152 341c803d Leszek Koltunski
  {
153
  const float h = 0.7;
154
  float signV = 2.0*max(0.0,sign(v))-1.0;
155
  float c = ((1.0-h)*(h-1.0)*u_Depth*u_Depth)/(v-signV*(2.0*h-1.0)*u_Depth) +signV*u_Depth;
156
  float b = max(0.0,sign(abs(v)-h*u_Depth));
157
158
  v = b*c+(1.0-b)*v; // Avoid branching: if abs(v)>h*u_Depth, then v=c; otherwise v=v.
159
  }
160
161 6a06a912 Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
162 341c803d Leszek Koltunski
// DEFORM EFFECT
163
//
164 cd174a64 Leszek Koltunski
// Deform the whole shape of the Object by force V
165 6a06a912 Leszek Koltunski
// 
166 cd174a64 Leszek Koltunski
// If the point of application (Sx,Sy) is on the edge of the Object, then:
167 6a06a912 Leszek Koltunski
// a) ignore Vz
168 cd174a64 Leszek Koltunski
// b) change shape of the whole Object in the following way:
169
//    Suppose the upper-left corner of the Object rectangle is point L, upper-right - R, force vector V is applied to point M on the upper edge,
170
//    width of the Object = w, height = h, |LM| = Wl, |MR| = Wr, force vector V=(Vx,Vy). Also let H = h/(h+Vy)
171 6a06a912 Leszek Koltunski
//
172
//    Let now L' and R' be points such that vec(LL') = Wr/w * vec(V) and vec(RR') = Wl/w * vec(V)
173
//    now let Vl be a point on the line segment L --> M+vec(V) such that Vl(y) = L'(y)
174
//    and let Vr be a point on the line segment R --> M+vec(V) such that Vr(y) = R'(y)
175
//    
176
//    Now define points Fl and Fr, the points L and R will be moved to under force V, with Fl(y)=L'(y) and Fr(y)=R'(y) and |VrFr|/|VrR'| = |VlFl|/|VlL'| = H
177
//    Now notice that |VrR'| = |VlL'| = Wl*Wr / w   ( a little geometric puzzle! )
178
//
179
//    Then points L,R under force V move by vectors vec(Fl), vec(Fr) where
180
//    vec(Fl) = (Wr/w) * [ (Vx+Wl)-Wl*H, Vy ] = (Wr/w) * [ Wl*Vy / (h+Vy) + Vx, Vy ]
181
//    vec(Fr) = (Wl/w) * [ (Vx-Wr)+Wr*H, Vy ] = (Wl/w) * [-Wr*Vy / (h+Vy) + Vx, Vy ]
182
//
183 cd174a64 Leszek Koltunski
//    Lets now denote M+vec(V) = M'. The line segment LMR gets distorted to the curve Fl-M'-Fr. Let's now arbitrarilly decide that:
184 6a06a912 Leszek Koltunski
//    a) at point Fl the curve has to be parallel to line LM'
185
//    b) at point M' - to line LR
186
//    c) at point Fr - to line M'R
187
//
188
//    Now if Fl=(flx,fly) , M'=(mx,my) , Fr=(frx,fry); direction vector at Fl is (vx,vy) and at M' is (+c,0) where +c is some positive constant, then 
189
//    the parametric equations of the Fl--->M' section of the curve (which has to satisfy (X(0),Y(0)) = Fl, (X(1),Y(1))=M', (X'(0),Y'(0)) = (vx,vy), (X'(1),Y'(1)) = (+c,0)) is
190
//
191
//    X(t) = ( (mx-flx)-vx )t^2 + vx*t + flx                                  (*)
192
//    Y(t) = ( vy - 2(my-fly) )t^3 + ( 3(my-fly) -2vy )t^2 + vy*t + fly
193
//
194
//    Here we have to have X'(1) = 2(mx-flx)-vx which is positive <==> vx<2(mx-flx). We also have to have vy<2(my-fly) so that Y'(t)>0 (this is a must otherwise we have local loops!) 
195
//    Similarly for the Fr--->M' part of the curve we have the same equation except for the fact that this time we have to have X'(1)<0 so now we have to have vx>2(mx-flx).
196
//
197
//    If we are stretching the left or right edge of the bitmap then the only difference is that we have to have (X'(1),Y'(1)) = (0,+-c) with + or - c depending on which part of the curve
198
//    we are tracing. Then the parametric equation is
199
//
200
//    X(t) = ( vx - 2(mx-flx) )t^3 + ( 3(mx-flx) -2vx )t^2 + vx*t + flx
201
//    Y(t) = ( (my-fly)-vy )t^2 + vy*t + fly
202
//
203
//    If we are dragging the top edge:    
204
//
205 0318e7e3 Leszek Koltunski
//    Now point (x,u_objD.x) on the top edge will move by vector (X(t),Y(t)) where those functions are given by (*) and
206 cd174a64 Leszek Koltunski
//    t =  x < dSx ? (u_objD.x+x)/(u_objD.x+dSx) : (u_objD.x-x)/(u_objD.x-dSx)    (this is 'vec2 time' below in the code)
207 0318e7e3 Leszek Koltunski
//    Any point (x,y) will move by vector (a*X(t),a*Y(t)) where a is (y+u_objD.y)/(2*u_objD.y)
208 6a06a912 Leszek Koltunski
  
209
void deform(in int effect, inout vec4 v)
210
  {
211 fa6c352d Leszek Koltunski
  vec2 center = vUniforms[effect+1].yz;
212 cd174a64 Leszek Koltunski
  vec2 force = vUniforms[effect].xy;    // force = vec(MM')
213 6a06a912 Leszek Koltunski
  vec2 vert_vec, horz_vec; 
214 cd174a64 Leszek Koltunski
  vec2 signXY = sign(center-v.xy);
215
  vec2 time = (u_objD.xy+signXY*v.xy)/(u_objD.xy+signXY*center);
216
  vec2 factorV = vec2(0.5,0.5) + (center*v.xy)/(4.0*u_objD.xy*u_objD.xy);
217
  vec2 factorD = (u_objD.xy-signXY*center)/(2.0*u_objD.xy);
218
  vec2 vert_d = factorD.x*force;
219
  vec2 horz_d = factorD.y*force;
220
  float dot = dot(force,force);
221
  vec2 corr = 0.33 * (center+force+signXY*u_objD.xy) * dot / ( dot + (4.0*u_objD.x*u_objD.x) ); // .x = the vector tangent to X(t) at Fl = 0.3*vec(LM')  (or vec(RM') if signXY.x=-1).
222
                                                                                                // .y = the vector tangent to X(t) at Fb = 0.3*vec(BM')  (or vec(TM') if signXY.y=-1)
223
                                                                                                // the scalar: make the length of the speed vectors at Fl and Fr be 0 when force vector 'force' is zero
224
  vert_vec.x = ( force.x-vert_d.x-corr.x )*time.x*time.x + corr.x*time.x + vert_d.x;
225
  horz_vec.y = (-force.y+horz_d.y+corr.y )*time.y*time.y - corr.y*time.y - horz_d.y;
226
  vert_vec.y = (-3.0*vert_d.y+2.0*force.y )*time.x*time.x*time.x + (-3.0*force.y+5.0*vert_d.y )*time.x*time.x - vert_d.y*time.x - vert_d.y;
227
  horz_vec.x = ( 3.0*horz_d.x-2.0*force.x )*time.y*time.y*time.y + ( 3.0*force.x-5.0*horz_d.x )*time.y*time.y + horz_d.x*time.y + horz_d.x;
228 6a06a912 Leszek Koltunski
  
229 cd174a64 Leszek Koltunski
  v.xy += (factorV.y*vert_vec + factorV.x*horz_vec);
230 6a06a912 Leszek Koltunski
  }
231
232
//////////////////////////////////////////////////////////////////////////////////////////////
233 341c803d Leszek Koltunski
// DISTORT EFFECT
234 6a06a912 Leszek Koltunski
//
235
// Point (Px,Py) gets moved by vector (Wx,Wy,Wz) where Wx/Wy = Vx/Vy i.e. Wx=aVx and Wy=aVy where 
236
// a=Py/Sy (N --> when (Px,Py) is above (Sx,Sy)) or a=Px/Sx (W) or a=(w-Px)/(w-Sx) (E) or a=(h-Py)/(h-Sy) (S) 
237
// It remains to be computed which of the N,W,E or S case we have: answer: a = min[ Px/Sx , Py/Sy , (w-Px)/(w-Sx) , (h-Py)/(h-Sy) ]
238
// Computations above are valid for screen (0,0)x(w,h) but here we have (-w/2,-h/2)x(w/2,h/2)
239
//  
240
// the vertical part
241
// Let |(v.x,v.y),(ux,uy)| = |PS|, ux-v.x=dx,uy-v.y=dy, f(x) (0<=x<=|SX|) be the shape of the side of the bubble.
242
// H(v.x,v.y) = |PS|>|SX| ? 0 : f(|PX|)
243
// N(v.x,v.y) = |PS|>|SX| ? (0,0,1) : ( -(dx/|PS|)sin(beta), -(dy/|PS|)sin(beta), cos(beta) ) where tan(beta) is f'(|PX|) 
244
// ( i.e. normalize( dx, dy, -|PS|/f'(|PX|))         
245
//
246
// Now we also have to take into account the effect horizontal move by V=(u_dVx[i],u_dVy[i]) will have on the normal vector.
247
// Solution: 
248
// 1. Decompose the V into two subcomponents, one parallel to SX and another perpendicular.
249
// 2. Convince yourself (draw!) that the perpendicular component has no effect on normals.
250 30925500 Leszek Koltunski
// 3. The parallel component changes the length of |SX| by the factor of a=(|SX|-|Vpar|)/|SX| (where the length
251
//    can be negative depending on the direction)
252 6a06a912 Leszek Koltunski
// 4. that in turn leaves the x and y parts of the normal unchanged and multiplies the z component by a!
253
//
254
// |Vpar| = (u_dVx[i]*dx - u_dVy[i]*dy) / sqrt(ps_sq) = (Vx*dx-Vy*dy)/ sqrt(ps_sq)  (-Vy because y is inverted)
255
// a =  (|SX| - |Vpar|)/|SX| = 1 - |Vpar|/((sqrt(ps_sq)/(1-d)) = 1 - (1-d)*|Vpar|/sqrt(ps_sq) = 1-(1-d)*(Vx*dx-Vy*dy)/ps_sq 
256
//
257
// Side of the bubble
258
// 
259
// choose from one of the three bubble shapes: the cone, the thin bubble and the thick bubble          
260
// Case 1: 
261
// f(t) = t, i.e. f(x) = uz * x/|SX|   (a cone)
262
// -|PS|/f'(|PX|) = -|PS|*|SX|/uz but since ps_sq=|PS|^2 and d=|PX|/|SX| then |PS|*|SX| = ps_sq/(1-d)
263
// so finally -|PS|/f'(|PX|) = -ps_sq/(uz*(1-d))
264
//                    
265
// Case 2: 
266
// f(t) = 3t^2 - 2t^3 --> f(0)=0, f'(0)=0, f'(1)=0, f(1)=1 (the bell curve)
267
// here we have t = x/|SX| which makes f'(|PX|) = 6*uz*|PS|*|PX|/|SX|^3.
268
// so -|PS|/f'(|PX|) = (-|SX|^3)/(6uz|PX|) =  (-|SX|^2) / (6*uz*d) but
269
// d = |PX|/|SX| and ps_sq = |PS|^2 so |SX|^2 = ps_sq/(1-d)^2
270
// so finally -|PS|/f'(|PX|) = -ps_sq/ (6uz*d*(1-d)^2)
271
//                  
272
// Case 3:
273 73af5285 Leszek Koltunski
// f(t) = 3t^4-8t^3+6t^2 would be better as this satisfies f(0)=0, f'(0)=0, f'(1)=0, f(1)=1,
274 30925500 Leszek Koltunski
// f(0.5)=0.7 and f'(t)= t(t-1)^2 >=0 for t>=0 so this produces a fuller, thicker bubble!
275 6a06a912 Leszek Koltunski
// then -|PS|/f'(|PX|) = (-|PS|*|SX)) / (12uz*d*(d-1)^2) but |PS|*|SX| = ps_sq/(1-d) (see above!) 
276
// so finally -|PS|/f'(|PX|) = -ps_sq/ (12uz*d*(1-d)^3)  
277
//
278
// Now, new requirement: we have to be able to add up normal vectors, i.e. distort already distorted surfaces.
279 73af5285 Leszek Koltunski
// If a surface is given by z = f(x,y), then the normal vector at (x0,y0) is given by (-df/dx (x0,y0), -df/dy (x0,y0), 1 ).
280 6a06a912 Leszek Koltunski
// so if we have two surfaces defined by f1(x,y) and f2(x,y) with their normals expressed as (f1x,f1y,1) and (f2x,f2y,1) 
281 73af5285 Leszek Koltunski
// then the normal to g = f1+f2 is simply given by (f1x+f2x,f1y+f2y,1), i.e. if the third components are equal, then we
282
// can simply add up the first and second components.
283 6a06a912 Leszek Koltunski
//
284 30925500 Leszek Koltunski
// Thus we actually want to compute N(v.x,v.y) = a*(-(dx/|PS|)*f'(|PX|), -(dy/|PS|)*f'(|PX|), 1) and keep adding
285
// the first two components. (a is the horizontal part)
286 6a06a912 Leszek Koltunski
        
287
void distort(in int effect, inout vec4 v, inout vec4 n)
288
  {
289 fa6c352d Leszek Koltunski
  vec2 center = vUniforms[effect+1].yz;
290 4fde55a0 Leszek Koltunski
  vec2 ps = center-v.xy;
291 a7067deb Leszek Koltunski
  vec3 force = vUniforms[effect].xyz;
292 4fde55a0 Leszek Koltunski
  float d = degree(vUniforms[effect+2],center,ps);
293 a7067deb Leszek Koltunski
  float denom = dot(ps+(1.0-d)*force.xy,ps);
294
  float one_over_denom = 1.0/(denom-0.001*(sign(denom)-1.0));          // = denom==0 ? 1000:1/denom;
295 30925500 Leszek Koltunski
296 a7067deb Leszek Koltunski
  //v.z += force.z*d;                                                  // cone
297
  //b = -(force.z*(1.0-d))*one_over_denom;                             //
298 6a06a912 Leszek Koltunski
        
299 a7067deb Leszek Koltunski
  //v.z += force.z*d*d*(3.0-2.0*d);                                    // thin bubble
300
  //b = -(6.0*force.z*d*(1.0-d)*(1.0-d))*one_over_denom;               //
301 6a06a912 Leszek Koltunski
        
302 a7067deb Leszek Koltunski
  v.z += force.z*d*d*(3.0*d*d -8.0*d +6.0);                            // thick bubble
303
  float b = -(12.0*force.z*d*(1.0-d)*(1.0-d)*(1.0-d))*one_over_denom;  //
304 6a06a912 Leszek Koltunski
                
305 a7067deb Leszek Koltunski
  v.xy += d*force.xy;
306
  n.xy += n.z*b*ps;
307 6a06a912 Leszek Koltunski
  }
308
 
309
//////////////////////////////////////////////////////////////////////////////////////////////
310 341c803d Leszek Koltunski
// SINK EFFECT
311
//
312 82ee855a Leszek Koltunski
// Pull P=(v.x,v.y) towards center of the effect with P' = P + (1-h)*dist(S-P)
313
// when h>1 we are pushing points away from S: P' = P + (1/h-1)*dist(S-P)
314 6a06a912 Leszek Koltunski
 
315
void sink(in int effect,inout vec4 v)
316
  {
317 fa6c352d Leszek Koltunski
  vec2 center = vUniforms[effect+1].yz;
318 4fde55a0 Leszek Koltunski
  vec2 ps = center-v.xy;
319 6a06a912 Leszek Koltunski
  float h = vUniforms[effect].x;
320 4fde55a0 Leszek Koltunski
  float t = degree(vUniforms[effect+2],center,ps) * (1.0-h)/max(1.0,h);
321 6a06a912 Leszek Koltunski
  
322
  v.xy += t*ps;           
323
  }
324
325 82ee855a Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
326
// PINCH EFFECT
327
//
328
// Pull P=(v.x,v.y) towards the line that
329
// a) passes through the center of the effect
330
// b) forms angle defined in the 2nd interpolated value with the X-axis
331
// with P' = P + (1-h)*dist(line to P)
332
// when h>1 we are pushing points away from S: P' = P + (1/h-1)*dist(line to P)
333
334
void pinch(in int effect,inout vec4 v)
335
  {
336
  vec2 center = vUniforms[effect+1].yz;
337
  vec2 ps = center-v.xy;
338
  float h = vUniforms[effect].x;
339
  float t = degree(vUniforms[effect+2],center,ps) * (1.0-h)/max(1.0,h);
340
  float angle = vUniforms[effect].y;
341
  vec2 dir = vec2(sin(angle),-cos(angle));
342
343
  v.xy += t*dot(ps,dir)*dir;
344
  }
345
346 6a06a912 Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
347 341c803d Leszek Koltunski
// SWIRL EFFECT
348 6a06a912 Leszek Koltunski
//
349
// Let d be the degree of the current vertex V with respect to center of the effect S and Region vRegion.
350
// This effect rotates the current vertex V by vInterpolated.x radians clockwise around the circle dilated 
351
// by (1-d) around the center of the effect S.
352
353 ff8ad0a7 Leszek Koltunski
void swirl(in int effect, inout vec4 v)
354 6a06a912 Leszek Koltunski
  {
355 fa6c352d Leszek Koltunski
  vec2 center  = vUniforms[effect+1].yz;
356 4fde55a0 Leszek Koltunski
  vec2 PS = center-v.xy;
357
  vec4 SO = vUniforms[effect+2];
358 6a06a912 Leszek Koltunski
  float d1_circle = degree_region(SO,PS);
359 4fde55a0 Leszek Koltunski
  float d1_bitmap = degree_bitmap(center,PS);
360 5b1c0f47 Leszek Koltunski
361
  float alpha = vUniforms[effect].x;
362
  float sinA = sin(alpha);
363
  float cosA = cos(alpha);
364
365 4fde55a0 Leszek Koltunski
  vec2 PS2 = vec2( PS.x*cosA+PS.y*sinA,-PS.x*sinA+PS.y*cosA ); // vector PS rotated by A radians clockwise around center.
366
  vec4 SG = (1.0-d1_circle)*SO;                                // coordinates of the dilated circle P is going to get rotated around
367
  float d2 = max(0.0,degree(SG,center,PS2));                   // make it a max(0,deg) because otherwise when center=left edge of the
368 20af7b69 Leszek Koltunski
                                                               // bitmap some points end up with d2<0 and they disappear off view.
369 4fde55a0 Leszek Koltunski
  v.xy += min(d1_circle,d1_bitmap)*(PS - PS2/(1.0-d2));        // if d2=1 (i.e P=center) we should have P unchanged. How to do it?
370
  }
371
372
//////////////////////////////////////////////////////////////////////////////////////////////
373
// WAVE EFFECT
374
//
375
// Directional sinusoidal wave effect.
376 73af5285 Leszek Koltunski
//
377
// This is an effect from a (hopefully!) generic family of effects of the form (vec3 V: |V|=1 , f(x,y) )  (*)
378
// i.e. effects defined by a unit vector and an arbitrary function. Those effects are defined to move each
379
// point (x,y,0) of the XY plane to the point (x,y,0) + V*f(x,y).
380
//
381
// In this case V is defined by angles A and B (sines and cosines of which are precomputed in
382
// EffectQueueVertex and passed in the uniforms).
383
// Let's move V to start at the origin O, let point C be the endpoint of V, and let C' be C's projection
384
// to the XY plane. Then A is defined to be the angle C0C' and angle B is the angle C'O(axisY).
385
//
386
// Also, in this case f(x,y) = amplitude*sin(x/length), with those 2 parameters passed in uniforms.
387
//
388 57297c51 Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
389 73af5285 Leszek Koltunski
// How to compute any generic effect of type (*)
390 57297c51 Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
391 73af5285 Leszek Koltunski
//
392
// By definition, the vertices move by f(x,y)*V.
393
//
394
// Normals are much more complicated.
395 57297c51 Leszek Koltunski
// Let angle X be the angle (0,Vy,Vz)(0,Vy,0)(Vx,Vy,Vz).
396
// Let angle Y be the angle (Vx,0,Vz)(Vx,0,0)(Vx,Vy,Vz).
397 73af5285 Leszek Koltunski
//
398
// Then it can be shown that the resulting surface, at point to which point (x0,y0,0) got moved to,
399
// has 2 tangent vectors given by
400
//
401 c6ea3680 Leszek Koltunski
// SX = (1.0+cosX*fx , cosY*sinX*fx , |sinY|*sinX*fx);  (**)
402
// SY = (cosX*sinY*fy , 1.0+cosY*fy , |sinX|*sinY*fy);  (***)
403 73af5285 Leszek Koltunski
//
404
// and then obviously the normal N is given by N= SX x SY .
405
//
406
// We still need to remember the note from the distort function about adding up normals:
407
// we first need to 'normalize' the normals to make their third components equal, and then we
408
// simply add up the first and the second component while leaving the third unchanged.
409
//
410
// How to see facts (**) and (***) ? Briefly:
411
// a) compute the 2D analogon and conclude that in this case the tangent SX is given by
412
//    SX = ( cosA*f'(x) +1, sinA*f'(x) )    (where A is the angle vector V makes with X axis )
413
// b) cut the resulting surface with plane P which
414
//    - includes vector V
415
//    - crosses plane XY along line parallel to X axis
416
// c) apply the 2D analogon and notice that the tangent vector to the curve that is the common part of P
417
//    and our surface (I am talking about the tangent vector which belongs to P) is given by
418 c6ea3680 Leszek Koltunski
//    (1+cosX*fx,0,sinX*fx) rotated by angle (90-|Y|) (where angles X,Y are defined above) along vector (1,0,0).
419
//
420
//    Matrix of rotation:
421
//
422
//    |sinY|  cosY
423
//    -cosY  |sinY|
424
//
425 73af5285 Leszek Koltunski
// d) compute the above and see that this is equal precisely to SX from (**).
426
// e) repeat points b,c,d in direction Y and come up with (***).
427 f256e1a5 Leszek Koltunski
//
428 5b1c0f47 Leszek Koltunski
//////////////////////////////////////////////////////////////////////////////////////////////
429 f256e1a5 Leszek Koltunski
// Note: we should avoid passing certain combinations of parameters to this function. One such known
430
// combination is ( A: small but positive, B: any, amplitude >= length ).
431
// In this case, certain 'unlucky' points have their normals almost horizontal (they got moved by (almost!)
432
// amplitude, and other point length (i.e. <=amplitude) away got moved by 0, so the slope in this point is
433
// very steep). Visual effect is: vast majority of surface pretty much unchanged, but random 'unlucky'
434
// points very dark)
435
//
436
// Generally speaking I'd keep to amplitude < length, as the opposite case has some other problems as well.
437 4fde55a0 Leszek Koltunski
438 9ea4f88f Leszek Koltunski
void wave(in int effect, inout vec4 v, inout vec4 n)
439 4fde55a0 Leszek Koltunski
  {
440 fa6c352d Leszek Koltunski
  vec2 center     = vUniforms[effect+1].yz;
441 02ef26bc Leszek Koltunski
  float amplitude = vUniforms[effect  ].x;
442 d0c902b8 Leszek Koltunski
  float length    = vUniforms[effect  ].y;
443 02ef26bc Leszek Koltunski
444 06d71892 Leszek Koltunski
  vec2 ps = center - v.xy;
445 9ea4f88f Leszek Koltunski
  float deg = amplitude*degree_region(vUniforms[effect+2],ps);
446 815869cb Leszek Koltunski
447 39b80df0 Leszek Koltunski
  if( deg != 0.0 && length != 0.0 )
448 9ea4f88f Leszek Koltunski
    {
449 ea16dc89 Leszek Koltunski
    float phase = vUniforms[effect  ].z;
450 350cc2f5 Leszek Koltunski
    float alpha = vUniforms[effect  ].w;
451
    float beta  = vUniforms[effect+1].x;
452 5b1c0f47 Leszek Koltunski
453
    float sinA = sin(alpha);
454
    float cosA = cos(alpha);
455
    float sinB = sin(beta);
456
    float cosB = cos(beta);
457 39b80df0 Leszek Koltunski
458 ea16dc89 Leszek Koltunski
    float angle= 1.578*(ps.x*cosB-ps.y*sinB) / length + phase;
459 57297c51 Leszek Koltunski
460 350cc2f5 Leszek Koltunski
    vec3 dir= vec3(sinB*cosA,cosB*cosA,sinA);
461 39b80df0 Leszek Koltunski
462
    v.xyz += sin(angle)*deg*dir;
463
464 73af5285 Leszek Koltunski
    if( n.z != 0.0 )
465
      {
466
      float sqrtX = sqrt(dir.y*dir.y + dir.z*dir.z);
467
      float sqrtY = sqrt(dir.x*dir.x + dir.z*dir.z);
468 39b80df0 Leszek Koltunski
469 73af5285 Leszek Koltunski
      float sinX = ( sqrtY==0.0 ? 0.0 : dir.z / sqrtY);
470
      float cosX = ( sqrtY==0.0 ? 1.0 : dir.x / sqrtY);
471
      float sinY = ( sqrtX==0.0 ? 0.0 : dir.z / sqrtX);
472
      float cosY = ( sqrtX==0.0 ? 1.0 : dir.y / sqrtX);
473 39b80df0 Leszek Koltunski
474 57297c51 Leszek Koltunski
      float abs_z = dir.z <0.0 ? -(sinX*sinY) : (sinX*sinY);
475 c6ea3680 Leszek Koltunski
476 73af5285 Leszek Koltunski
      float tmp = 1.578*cos(angle)*deg/length;
477 39b80df0 Leszek Koltunski
478 57297c51 Leszek Koltunski
      float fx =-cosB*tmp;
479 73af5285 Leszek Koltunski
      float fy = sinB*tmp;
480 39b80df0 Leszek Koltunski
481 57297c51 Leszek Koltunski
      vec3 sx = vec3 (1.0+cosX*fx,cosY*sinX*fx,abs_z*fx);
482
      vec3 sy = vec3 (cosX*sinY*fy,1.0+cosY*fy,abs_z*fy);
483 39b80df0 Leszek Koltunski
484 73af5285 Leszek Koltunski
      vec3 normal = cross(sx,sy);
485 39b80df0 Leszek Koltunski
486 fe3cee39 Leszek Koltunski
      if( normal.z<=0.0 )                   // Why this bizarre shit rather than the straightforward
487
        {                                   //
488
        normal.x= 0.0;                      // if( normal.z>0.0 )
489
        normal.y= 0.0;                      //   {
490
        normal.z= 1.0;                      //   n.x = (n.x*normal.z + n.z*normal.x);
491
        }                                   //   n.y = (n.y*normal.z + n.z*normal.y);
492
                                            //   n.z = (n.z*normal.z);
493
                                            //   }
494
      n.x = (n.x*normal.z + n.z*normal.x);  //
495
      n.y = (n.y*normal.z + n.z*normal.y);  // ? Because if we do the above, my shitty Nexus4 crashes
496
      n.z = (n.z*normal.z);                 // during shader compilation!
497 39b80df0 Leszek Koltunski
      }
498 9ea4f88f Leszek Koltunski
    }
499 6a06a912 Leszek Koltunski
  }
500
501
#endif
502
503
//////////////////////////////////////////////////////////////////////////////////////////////
504
  		  
505
void main()                                                 	
506
  {              
507 0318e7e3 Leszek Koltunski
  vec4 v = vec4( 2.0*u_objD*a_Position,1.0 );
508 6a06a912 Leszek Koltunski
  vec4 n = vec4(a_Normal,0.0);
509
510
#if NUM_VERTEX>0
511
  for(int i=0; i<vNumEffects; i++)
512
    {
513
         if( vType[i]==DISTORT) distort(3*i,v,n);
514 341c803d Leszek Koltunski
    else if( vType[i]==DEFORM ) deform (3*i,v);
515
    else if( vType[i]==SINK   ) sink   (3*i,v);
516 82ee855a Leszek Koltunski
    else if( vType[i]==PINCH  ) pinch  (3*i,v);
517 341c803d Leszek Koltunski
    else if( vType[i]==SWIRL  ) swirl  (3*i,v);
518 9ea4f88f Leszek Koltunski
    else if( vType[i]==WAVE   ) wave   (3*i,v,n);
519 6a06a912 Leszek Koltunski
    }
520
 
521 291705f6 Leszek Koltunski
  restrictZ(v.z);
522 6a06a912 Leszek Koltunski
#endif
523
   
524 77fcb24d Leszek Koltunski
  v_Position      = v.xyz;
525 2dacdeb2 Leszek Koltunski
  v_TexCoordinate = a_TexCoordinate;
526 6a06a912 Leszek Koltunski
  v_Normal        = normalize(vec3(u_MVMatrix*n));
527
  gl_Position     = u_MVPMatrix*v;      
528 d333eb6b Leszek Koltunski
  }