]> de.git.xonotic.org Git - xonotic/netradiant.git/blob - radiant/brush_primit.cpp
* brush primitive patch by divVerent
[xonotic/netradiant.git] / radiant / brush_primit.cpp
1 /*
2 Copyright (C) 1999-2007 id Software, Inc. and contributors.
3 For a list of contributors, see the accompanying CONTRIBUTORS file.
4
5 This file is part of GtkRadiant.
6
7 GtkRadiant is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2 of the License, or
10 (at your option) any later version.
11
12 GtkRadiant is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 GNU General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with GtkRadiant; if not, write to the Free Software
19 Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
20 */
21
22 #include "stdafx.h"
23
24 // compute a determinant using Sarrus rule
25 //++timo "inline" this with a macro
26 // NOTE : the three vec3_t are understood as columns of the matrix
27 vec_t SarrusDet(vec3_t a, vec3_t b, vec3_t c)
28 {
29         return a[0]*b[1]*c[2]+b[0]*c[1]*a[2]+c[0]*a[1]*b[2]
30                 -c[0]*b[1]*a[2]-a[1]*b[0]*c[2]-a[0]*b[2]*c[1];
31 }
32
33 // in many case we know three points A,B,C in two axis base B1 and B2
34 // and we want the matrix M so that A(B1) = T * A(B2)
35 // NOTE: 2D homogeneous space stuff
36 // NOTE: we don't do any check to see if there's a solution or we have a particular case .. need to make sure before calling
37 // NOTE: the third coord of the A,B,C point is ignored
38 // NOTE: see the commented out section to fill M and D
39 //++timo TODO: update the other members to use this when possible
40 void MatrixForPoints( vec3_t M[3], vec3_t D[2], brushprimit_texdef_t *T )
41 {
42 //      vec3_t M[3]; // columns of the matrix .. easier that way (the indexing is not standard! it's column-line .. later computations are easier that way)
43         vec_t det;
44 //      vec3_t D[2];
45         M[2][0]=1.0f; M[2][1]=1.0f; M[2][2]=1.0f;
46 #if 0
47         // fill the data vectors
48         M[0][0]=A2[0]; M[0][1]=B2[0]; M[0][2]=C2[0];
49         M[1][0]=A2[1]; M[1][1]=B2[1]; M[1][2]=C2[1];
50         M[2][0]=1.0f; M[2][1]=1.0f; M[2][2]=1.0f;
51         D[0][0]=A1[0];
52         D[0][1]=B1[0];
53         D[0][2]=C1[0];
54         D[1][0]=A1[1];
55         D[1][1]=B1[1];
56         D[1][2]=C1[1];
57 #endif
58         // solve
59         det = SarrusDet( M[0], M[1], M[2] );
60         T->coords[0][0] = SarrusDet( D[0], M[1], M[2] ) / det;
61         T->coords[0][1] = SarrusDet( M[0], D[0], M[2] ) / det;
62         T->coords[0][2] = SarrusDet( M[0], M[1], D[0] ) / det;
63         T->coords[1][0] = SarrusDet( D[1], M[1], M[2] ) / det;
64         T->coords[1][1] = SarrusDet( M[0], D[1], M[2] ) / det;
65         T->coords[1][2] = SarrusDet( M[0], M[1], D[1] ) / det;
66 }
67
68 //++timo replace everywhere texX by texS etc. ( ----> and in q3map !)
69 // NOTE : ComputeAxisBase here and in q3map code must always BE THE SAME !
70 // WARNING : special case behaviour of atan2(y,x) <-> atan(y/x) might not be the same everywhere when x == 0
71 // rotation by (0,RotY,RotZ) assigns X to normal
72 void ComputeAxisBase(vec3_t normal,vec3_t texS,vec3_t texT )
73 {
74         vec_t RotY,RotZ;
75         // do some cleaning
76         if (fabs(normal[0])<1e-6)
77                 normal[0]=0.0f;
78         if (fabs(normal[1])<1e-6)
79                 normal[1]=0.0f;
80         if (fabs(normal[2])<1e-6)
81                 normal[2]=0.0f;
82         RotY=-atan2(normal[2],sqrt(normal[1]*normal[1]+normal[0]*normal[0]));
83         RotZ=atan2(normal[1],normal[0]);
84         // rotate (0,1,0) and (0,0,1) to compute texS and texT
85         texS[0]=-sin(RotZ);
86         texS[1]=cos(RotZ);
87         texS[2]=0;
88         // the texT vector is along -Z ( T texture coorinates axis )
89         texT[0]=-sin(RotY)*cos(RotZ);
90         texT[1]=-sin(RotY)*sin(RotZ);
91         texT[2]=-cos(RotY);
92 }
93
94 void FaceToBrushPrimitFace(face_t *f)
95 {
96         vec3_t texX,texY;
97         vec3_t proj;
98         // ST of (0,0) (1,0) (0,1)
99         vec_t ST[3][5]; // [ point index ] [ xyz ST ]
100         //++timo not used as long as brushprimit_texdef and texdef are static
101 /*      f->brushprimit_texdef.contents=f->texdef.contents;
102         f->brushprimit_texdef.flags=f->texdef.flags;
103         f->brushprimit_texdef.value=f->texdef.value;
104         strcpy(f->brushprimit_texdef.name,f->texdef.name); */
105 #ifdef DBG_BP
106         if ( f->plane.normal[0]==0.0f && f->plane.normal[1]==0.0f && f->plane.normal[2]==0.0f )
107         {
108                 Sys_Printf("Warning : f->plane.normal is (0,0,0) in FaceToBrushPrimitFace\n");
109         }
110         // check d_texture
111         if (!f->d_texture)
112         {
113                 Sys_Printf("Warning : f.d_texture is NULL in FaceToBrushPrimitFace\n");
114                 return;
115         }
116 #endif
117         // compute axis base
118         ComputeAxisBase(f->plane.normal,texX,texY);
119         // compute projection vector
120         VectorCopy(f->plane.normal,proj);
121         VectorScale(proj,f->plane.dist,proj);
122         // (0,0) in plane axis base is (0,0,0) in world coordinates + projection on the affine plane
123         // (1,0) in plane axis base is texX in world coordinates + projection on the affine plane
124         // (0,1) in plane axis base is texY in world coordinates + projection on the affine plane
125         // use old texture code to compute the ST coords of these points
126         VectorCopy(proj,ST[0]);
127         EmitTextureCoordinates(ST[0], f->d_texture, f);
128         VectorCopy(texX,ST[1]);
129         VectorAdd(ST[1],proj,ST[1]);
130         EmitTextureCoordinates(ST[1], f->d_texture, f);
131         VectorCopy(texY,ST[2]);
132         VectorAdd(ST[2],proj,ST[2]);
133         EmitTextureCoordinates(ST[2], f->d_texture, f);
134         // compute texture matrix
135         f->brushprimit_texdef.coords[0][2]=ST[0][3];
136         f->brushprimit_texdef.coords[1][2]=ST[0][4];
137         f->brushprimit_texdef.coords[0][0]=ST[1][3]-f->brushprimit_texdef.coords[0][2];
138         f->brushprimit_texdef.coords[1][0]=ST[1][4]-f->brushprimit_texdef.coords[1][2];
139         f->brushprimit_texdef.coords[0][1]=ST[2][3]-f->brushprimit_texdef.coords[0][2];
140         f->brushprimit_texdef.coords[1][1]=ST[2][4]-f->brushprimit_texdef.coords[1][2];
141 }
142
143 // compute texture coordinates for the winding points
144 void EmitBrushPrimitTextureCoordinates(face_t * f, winding_t * w)
145 {
146         vec3_t texX,texY;
147         vec_t x,y;
148         // compute axis base
149         ComputeAxisBase(f->plane.normal,texX,texY);
150         // in case the texcoords matrix is empty, build a default one
151         // same behaviour as if scale[0]==0 && scale[1]==0 in old code
152         if (f->brushprimit_texdef.coords[0][0]==0 && f->brushprimit_texdef.coords[1][0]==0 && f->brushprimit_texdef.coords[0][1]==0 && f->brushprimit_texdef.coords[1][1]==0)
153         {
154                 f->brushprimit_texdef.coords[0][0] = 1.0f;
155                 f->brushprimit_texdef.coords[1][1] = 1.0f;
156                 ConvertTexMatWithQTexture( &f->brushprimit_texdef, NULL, &f->brushprimit_texdef, f->d_texture );
157         }
158         int i;
159     for (i=0 ; i<w->numpoints ; i++)
160         {
161                 x=DotProduct(w->points[i],texX);
162                 y=DotProduct(w->points[i],texY);
163 #ifdef DBG_BP
164                 if (g_qeglobals.bNeedConvert)
165                 {
166                         // check we compute the same ST as the traditional texture computation used before
167                         vec_t S=f->brushprimit_texdef.coords[0][0]*x+f->brushprimit_texdef.coords[0][1]*y+f->brushprimit_texdef.coords[0][2];
168                         vec_t T=f->brushprimit_texdef.coords[1][0]*x+f->brushprimit_texdef.coords[1][1]*y+f->brushprimit_texdef.coords[1][2];
169                         if ( fabs(S-w->points[i][3])>1e-2 || fabs(T-w->points[i][4])>1e-2 )
170                         {
171                                 if ( fabs(S-w->points[i][3])>1e-4 || fabs(T-w->points[i][4])>1e-4 )
172                                         Sys_Printf("Warning : precision loss in brush -> brush primitive texture computation\n");
173                                 else
174                                         Sys_Printf("Warning : brush -> brush primitive texture computation bug detected\n");
175                         }
176                 }
177 #endif
178                 w->points[i][3]=f->brushprimit_texdef.coords[0][0]*x+f->brushprimit_texdef.coords[0][1]*y+f->brushprimit_texdef.coords[0][2];
179                 w->points[i][4]=f->brushprimit_texdef.coords[1][0]*x+f->brushprimit_texdef.coords[1][1]*y+f->brushprimit_texdef.coords[1][2];
180         }
181 }
182
183 // compute a fake shift scale rot representation from the texture matrix
184 // these shift scale rot values are to be understood in the local axis base
185 void TexMatToFakeTexCoords( vec_t texMat[2][3], float shift[2], float *rot, float scale[2] )
186 {
187 #ifdef DBG_BP
188         // check this matrix is orthogonal
189         if (fabs(texMat[0][0]*texMat[0][1]+texMat[1][0]*texMat[1][1])>ZERO_EPSILON)
190                 Sys_Printf("Warning : non orthogonal texture matrix in TexMatToFakeTexCoords\n");
191 #endif
192         scale[0]=sqrt(texMat[0][0]*texMat[0][0]+texMat[1][0]*texMat[1][0]);
193         scale[1]=sqrt(texMat[0][1]*texMat[0][1]+texMat[1][1]*texMat[1][1]);
194 #ifdef DBG_BP
195         if (scale[0]<ZERO_EPSILON || scale[1]<ZERO_EPSILON)
196                 Sys_Printf("Warning : unexpected scale==0 in TexMatToFakeTexCoords\n");
197 #endif
198         // compute rotate value
199         if (fabs(texMat[0][0])<ZERO_EPSILON)
200         {
201 #ifdef DBG_BP
202                 // check brushprimit_texdef[1][0] is not zero
203                 if (fabs(texMat[1][0])<ZERO_EPSILON)
204                         Sys_Printf("Warning : unexpected texdef[1][0]==0 in TexMatToFakeTexCoords\n");
205 #endif
206                 // rotate is +-90
207                 if (texMat[1][0]>0)
208                         *rot=90.0f;
209                 else
210                         *rot=-90.0f;
211         }
212         else
213         *rot = RAD2DEG( atan2( texMat[1][0], texMat[0][0] ) );
214         shift[0] = -texMat[0][2];
215         shift[1] = texMat[1][2];
216 }
217
218 // compute back the texture matrix from fake shift scale rot
219 // the matrix returned must be understood as a qtexture_t with width=2 height=2 ( the default one )
220 void FakeTexCoordsToTexMat( float shift[2], float rot, float scale[2], vec_t texMat[2][3] )
221 {
222         texMat[0][0] = scale[0] * cos( DEG2RAD( rot ) );
223         texMat[1][0] = scale[0] * sin( DEG2RAD( rot ) );
224         texMat[0][1] = -1.0f * scale[1] * sin( DEG2RAD( rot ) );
225         texMat[1][1] = scale[1] * cos( DEG2RAD( rot ) );
226         texMat[0][2] = -shift[0];
227         texMat[1][2] = shift[1];
228 }
229
230 // convert a texture matrix between two qtexture_t
231 // if NULL for qtexture_t, basic 2x2 texture is assumed ( straight mapping between s/t coordinates and geometric coordinates )
232 void ConvertTexMatWithQTexture( vec_t texMat1[2][3], qtexture_t *qtex1, vec_t texMat2[2][3], qtexture_t *qtex2 )
233 {
234         float s1,s2;
235         s1 = ( qtex1 ? static_cast<float>( qtex1->width ) : 2.0f ) / ( qtex2 ? static_cast<float>( qtex2->width ) : 2.0f );
236         s2 = ( qtex1 ? static_cast<float>( qtex1->height ) : 2.0f ) / ( qtex2 ? static_cast<float>( qtex2->height ) : 2.0f );
237         texMat2[0][0]=s1*texMat1[0][0];
238         texMat2[0][1]=s1*texMat1[0][1];
239         texMat2[0][2]=s1*texMat1[0][2];
240         texMat2[1][0]=s2*texMat1[1][0];
241         texMat2[1][1]=s2*texMat1[1][1];
242         texMat2[1][2]=s2*texMat1[1][2];
243 }
244
245 void ConvertTexMatWithQTexture( brushprimit_texdef_t *texMat1, qtexture_t *qtex1, brushprimit_texdef_t *texMat2, qtexture_t *qtex2 )
246 {
247   ConvertTexMatWithQTexture(texMat1->coords, qtex1, texMat2->coords, qtex2);
248 }
249
250 // used for texture locking
251 // will move the texture according to a geometric vector
252 void ShiftTextureGeometric_BrushPrimit(face_t *f, vec3_t delta)
253 {
254         vec3_t texS,texT;
255         vec_t tx,ty;
256         vec3_t M[3]; // columns of the matrix .. easier that way
257         vec_t det;
258         vec3_t D[2];
259         // compute plane axis base ( doesn't change with translation )
260         ComputeAxisBase( f->plane.normal, texS, texT );
261         // compute translation vector in plane axis base
262         tx = DotProduct( delta, texS );
263         ty = DotProduct( delta, texT );
264         // fill the data vectors
265         M[0][0]=tx; M[0][1]=1.0f+tx; M[0][2]=tx;
266         M[1][0]=ty; M[1][1]=ty; M[1][2]=1.0f+ty;
267         M[2][0]=1.0f; M[2][1]=1.0f; M[2][2]=1.0f;
268         D[0][0]=f->brushprimit_texdef.coords[0][2];
269         D[0][1]=f->brushprimit_texdef.coords[0][0]+f->brushprimit_texdef.coords[0][2];
270         D[0][2]=f->brushprimit_texdef.coords[0][1]+f->brushprimit_texdef.coords[0][2];
271         D[1][0]=f->brushprimit_texdef.coords[1][2];
272         D[1][1]=f->brushprimit_texdef.coords[1][0]+f->brushprimit_texdef.coords[1][2];
273         D[1][2]=f->brushprimit_texdef.coords[1][1]+f->brushprimit_texdef.coords[1][2];
274         // solve
275         det = SarrusDet( M[0], M[1], M[2] );
276         f->brushprimit_texdef.coords[0][0] = SarrusDet( D[0], M[1], M[2] ) / det;
277         f->brushprimit_texdef.coords[0][1] = SarrusDet( M[0], D[0], M[2] ) / det;
278         f->brushprimit_texdef.coords[0][2] = SarrusDet( M[0], M[1], D[0] ) / det;
279         f->brushprimit_texdef.coords[1][0] = SarrusDet( D[1], M[1], M[2] ) / det;
280         f->brushprimit_texdef.coords[1][1] = SarrusDet( M[0], D[1], M[2] ) / det;
281         f->brushprimit_texdef.coords[1][2] = SarrusDet( M[0], M[1], D[1] ) / det;
282 }
283
284 // shift a texture (texture adjustments) along it's current texture axes
285 // x and y are geometric values, which we must compute as ST increments
286 // this depends on the texture size and the pixel/texel ratio
287 void ShiftTextureRelative_BrushPrimit( face_t *f, float x, float y)
288 {
289   float s,t;
290   // as a ratio against texture size
291   // the scale of the texture is not relevant here (we work directly on a transformation from the base vectors)
292   s = (x * 2.0) / (float)f->d_texture->width;
293   t = (y * 2.0) / (float)f->d_texture->height;
294   f->brushprimit_texdef.coords[0][2] -= s;
295   f->brushprimit_texdef.coords[1][2] -= t;
296 }
297
298 // TTimo: FIXME: I don't like that, it feels broken
299 //   (and it's likely that it's not used anymore)
300 // best fitted 2D vector is x.X+y.Y
301 void ComputeBest2DVector( vec3_t v, vec3_t X, vec3_t Y, int &x, int &y )
302 {
303         double sx,sy;
304         sx = DotProduct( v, X );
305         sy = DotProduct( v, Y );
306         if ( fabs(sy) > fabs(sx) )
307   {
308                 x = 0;
309                 if ( sy > 0.0 )
310                         y =  1;
311                 else
312                         y = -1;
313         }
314         else
315         {
316                 y = 0;
317                 if ( sx > 0.0 )
318                         x =  1;
319                 else
320                         x = -1;
321         }
322 }
323
324 //++timo FIXME quick'n dirty hack, doesn't care about current texture settings (angle)
325 // can be improved .. bug #107311
326 // mins and maxs are the face bounding box
327 //++timo fixme: we use the face info, mins and maxs are irrelevant
328 void Face_FitTexture_BrushPrimit( face_t *f, vec3_t mins, vec3_t maxs, int nHeight, int nWidth )
329 {
330         vec3_t BBoxSTMin, BBoxSTMax;
331         winding_t *w;
332         int i,j;
333         vec_t val;
334         vec3_t M[3],D[2];
335 //      vec3_t N[2],Mf[2];
336         brushprimit_texdef_t N;
337         vec3_t Mf[2];
338
339
340         // we'll be working on a standardized texture size
341 //      ConvertTexMatWithQTexture( &f->brushprimit_texdef, f->d_texture, &f->brushprimit_texdef, NULL );
342         // compute the BBox in ST coords
343         EmitBrushPrimitTextureCoordinates( f, f->face_winding );
344         ClearBounds( BBoxSTMin, BBoxSTMax );
345         w = f->face_winding;
346         for (i=0 ; i<w->numpoints ; i++)
347         {
348                 // AddPointToBounds in 2D on (S,T) coordinates
349                 for (j=0 ; j<2 ; j++)
350                 {
351                         val = w->points[i][j+3];
352                         if (val < BBoxSTMin[j])
353                                 BBoxSTMin[j] = val;
354                         if (val > BBoxSTMax[j])
355                                 BBoxSTMax[j] = val;
356                 }
357         }
358         // we have the three points of the BBox (BBoxSTMin[0].BBoxSTMin[1]) (BBoxSTMax[0],BBoxSTMin[1]) (BBoxSTMin[0],BBoxSTMax[1]) in ST space
359         // the BP matrix we are looking for gives (0,0) (nwidth,0) (0,nHeight) coordinates in (Sfit,Tfit) space to these three points
360         // we have A(Sfit,Tfit) = (0,0) = Mf * A(TexS,TexT) = N * M * A(TexS,TexT) = N * A(S,T)
361         // so we solve the system for N and then Mf = N * M
362         M[0][0] = BBoxSTMin[0]; M[0][1] = BBoxSTMax[0]; M[0][2] = BBoxSTMin[0];
363         M[1][0] = BBoxSTMin[1]; M[1][1] = BBoxSTMin[1]; M[1][2] = BBoxSTMax[1];
364         D[0][0] = 0.0f; D[0][1] = nWidth; D[0][2] = 0.0f;
365         D[1][0] = 0.0f; D[1][1] = 0.0f; D[1][2] = nHeight;
366         MatrixForPoints( M, D, &N );
367
368 #if 0
369         // FIT operation gives coordinates of three points of the bounding box in (S',T'), our target axis base
370         // A(S',T')=(0,0) B(S',T')=(nWidth,0) C(S',T')=(0,nHeight)
371         // and we have them in (S,T) axis base: A(S,T)=(BBoxSTMin[0],BBoxSTMin[1]) B(S,T)=(BBoxSTMax[0],BBoxSTMin[1]) C(S,T)=(BBoxSTMin[0],BBoxSTMax[1])
372         // we compute the N transformation so that: A(S',T') = N * A(S,T)
373         VectorSet( N[0], (BBoxSTMax[0]-BBoxSTMin[0])/(float)nWidth, 0.0f, BBoxSTMin[0] );
374         VectorSet( N[1], 0.0f, (BBoxSTMax[1]-BBoxSTMin[1])/(float)nHeight, BBoxSTMin[1] );
375 #endif
376
377         // the final matrix is the product (Mf stands for Mfit)
378         Mf[0][0] = N.coords[0][0] * f->brushprimit_texdef.coords[0][0] + N.coords[0][1] * f->brushprimit_texdef.coords[1][0];
379         Mf[0][1] = N.coords[0][0] * f->brushprimit_texdef.coords[0][1] + N.coords[0][1] * f->brushprimit_texdef.coords[1][1];
380         Mf[0][2] = N.coords[0][0] * f->brushprimit_texdef.coords[0][2] + N.coords[0][1] * f->brushprimit_texdef.coords[1][2] + N.coords[0][2];
381         Mf[1][0] = N.coords[1][0] * f->brushprimit_texdef.coords[0][0] + N.coords[1][1] * f->brushprimit_texdef.coords[1][0];
382         Mf[1][1] = N.coords[1][0] * f->brushprimit_texdef.coords[0][1] + N.coords[1][1] * f->brushprimit_texdef.coords[1][1];
383         Mf[1][2] = N.coords[1][0] * f->brushprimit_texdef.coords[0][2] + N.coords[1][1] * f->brushprimit_texdef.coords[1][2] + N.coords[1][2];
384         // copy back
385         VectorCopy( Mf[0], f->brushprimit_texdef.coords[0] );
386         VectorCopy( Mf[1], f->brushprimit_texdef.coords[1] );
387         // handle the texture size
388 //      ConvertTexMatWithQTexture( &f->brushprimit_texdef, NULL, &f->brushprimit_texdef, f->d_texture );
389 }
390
391 void BrushPrimitFaceToFace(face_t *f)
392 {
393 #if 0
394         // we have parsed brush primitives and need conversion back to standard format
395         // NOTE: converting back is a quick hack, there's some information lost and we can't do anything about it
396         // FIXME: if we normalize the texture matrix to a standard 2x2 size, we end up with wrong scaling
397         // I tried various tweaks, no luck .. seems shifting is lost
398         brushprimit_texdef_t aux;
399         ConvertTexMatWithQTexture( &face->brushprimit_texdef, face->d_texture, &aux, NULL );
400         TexMatToFakeTexCoords( aux.coords, face->texdef.shift, &face->texdef.rotate, face->texdef.scale );
401         face->texdef.scale[0]/=2.0;
402         face->texdef.scale[1]/=2.0;
403 #else
404         // new method by divVerent@alientrap.org: Shift and scale no longer get lost when opening a BP map in texdef mode.
405         vec3_t texX,texY;
406         vec3_t proj;
407         vec_t ST[3][5];
408
409         ComputeAxisBase(f->plane.normal,texX,texY);
410         VectorCopy(f->plane.normal,proj);
411         VectorScale(proj,f->plane.dist,proj);
412         VectorCopy(proj,ST[0]);
413         VectorCopy(texX,ST[1]);
414         VectorAdd(ST[1],proj,ST[1]);
415         VectorCopy(texY,ST[2]);
416         VectorAdd(ST[2],proj,ST[2]);
417
418         ST[0][3] = f->brushprimit_texdef.coords[0][2];
419         ST[0][4] = f->brushprimit_texdef.coords[1][2];
420         ST[1][3] = f->brushprimit_texdef.coords[0][0] + ST[0][3];
421         ST[1][4] = f->brushprimit_texdef.coords[1][0] + ST[0][4];
422         ST[2][3] = f->brushprimit_texdef.coords[0][1] + ST[0][3];
423         ST[2][4] = f->brushprimit_texdef.coords[1][1] + ST[0][4];
424
425         Face_TexdefFromTextureCoordinates(ST[0], ST[1], ST[2], f->d_texture, f);
426 #endif
427 }
428
429 // TEXTURE LOCKING -----------------------------------------------------------------------------------------------------
430 // (Relevant to the editor only?)
431
432 // internally used for texture locking on rotation and flipping
433 // the general algorithm is the same for both lockings, it's only the geometric transformation part that changes
434 // so I wanted to keep it in a single function
435 // if there are more linear transformations that need the locking, going to a C++ or code pointer solution would be best
436 // (but right now I want to keep brush_primit.cpp striclty C)
437
438 qboolean txlock_bRotation;
439
440 // rotation locking params
441 int txl_nAxis;
442 float txl_fDeg;
443 vec3_t txl_vOrigin;
444
445 // flip locking params
446 vec3_t txl_matrix[3];
447 vec3_t txl_origin;
448
449 void TextureLockTransformation_BrushPrimit(face_t *f)
450 {
451         vec3_t Orig,texS,texT;        // axis base of initial plane
452         // used by transformation algo
453         vec3_t temp; int j;
454         vec3_t vRotate;                                 // rotation vector
455
456         vec3_t rOrig,rvecS,rvecT;     // geometric transformation of (0,0) (1,0) (0,1) { initial plane axis base }
457         vec3_t rNormal,rtexS,rtexT;   // axis base for the transformed plane
458         vec3_t lOrig,lvecS,lvecT;       // [2] are not used ( but usefull for debugging )
459         vec3_t M[3];
460         vec_t det;
461         vec3_t D[2];
462
463         // compute plane axis base
464         ComputeAxisBase( f->plane.normal, texS, texT );
465         VectorSet(Orig, 0.0f, 0.0f, 0.0f);
466
467         // compute coordinates of (0,0) (1,0) (0,1) ( expressed in initial plane axis base ) after transformation
468         // (0,0) (1,0) (0,1) ( expressed in initial plane axis base ) <-> (0,0,0) texS texT ( expressed world axis base )
469         // input: Orig, texS, texT (and the global locking params)
470         // ouput: rOrig, rvecS, rvecT, rNormal
471         if (txlock_bRotation) {
472                 // rotation vector
473                 VectorSet( vRotate, 0.0f, 0.0f, 0.0f );
474                 vRotate[txl_nAxis]=txl_fDeg;
475                 VectorRotateOrigin ( Orig, vRotate, txl_vOrigin, rOrig );
476                 VectorRotateOrigin ( texS, vRotate, txl_vOrigin, rvecS );
477                 VectorRotateOrigin ( texT, vRotate, txl_vOrigin, rvecT );
478                 // compute normal of plane after rotation
479                 VectorRotate ( f->plane.normal, vRotate, rNormal );
480         }
481         else
482         {
483                 VectorSubtract (Orig, txl_origin, temp);
484                 for (j=0 ; j<3 ; j++)
485                 rOrig[j] = DotProduct(temp, txl_matrix[j]) + txl_origin[j];
486                 VectorSubtract (texS, txl_origin, temp);
487                 for (j=0 ; j<3 ; j++)
488                 rvecS[j] = DotProduct(temp, txl_matrix[j]) + txl_origin[j];
489                 VectorSubtract (texT, txl_origin, temp);
490                 for (j=0 ; j<3 ; j++)
491                 rvecT[j] = DotProduct(temp, txl_matrix[j]) + txl_origin[j];
492                 // we also need the axis base of the target plane, apply the transformation matrix to the normal too..
493                 for (j=0 ; j<3 ; j++)
494                 rNormal[j] = DotProduct(f->plane.normal, txl_matrix[j]);
495         }
496
497         // compute rotated plane axis base
498         ComputeAxisBase( rNormal, rtexS, rtexT );
499         // compute S/T coordinates of the three points in rotated axis base ( in M matrix )
500         lOrig[0] = DotProduct( rOrig, rtexS );
501         lOrig[1] = DotProduct( rOrig, rtexT );
502         lvecS[0] = DotProduct( rvecS, rtexS );
503         lvecS[1] = DotProduct( rvecS, rtexT );
504         lvecT[0] = DotProduct( rvecT, rtexS );
505         lvecT[1] = DotProduct( rvecT, rtexT );
506         M[0][0] = lOrig[0]; M[1][0] = lOrig[1]; M[2][0] = 1.0f;
507         M[0][1] = lvecS[0]; M[1][1] = lvecS[1]; M[2][1] = 1.0f;
508         M[0][2] = lvecT[0]; M[1][2] = lvecT[1]; M[2][2] = 1.0f;
509         // fill data vector
510         D[0][0]=f->brushprimit_texdef.coords[0][2];
511         D[0][1]=f->brushprimit_texdef.coords[0][0]+f->brushprimit_texdef.coords[0][2];
512         D[0][2]=f->brushprimit_texdef.coords[0][1]+f->brushprimit_texdef.coords[0][2];
513         D[1][0]=f->brushprimit_texdef.coords[1][2];
514         D[1][1]=f->brushprimit_texdef.coords[1][0]+f->brushprimit_texdef.coords[1][2];
515         D[1][2]=f->brushprimit_texdef.coords[1][1]+f->brushprimit_texdef.coords[1][2];
516         // solve
517         det = SarrusDet( M[0], M[1], M[2] );
518         f->brushprimit_texdef.coords[0][0] = SarrusDet( D[0], M[1], M[2] ) / det;
519         f->brushprimit_texdef.coords[0][1] = SarrusDet( M[0], D[0], M[2] ) / det;
520         f->brushprimit_texdef.coords[0][2] = SarrusDet( M[0], M[1], D[0] ) / det;
521         f->brushprimit_texdef.coords[1][0] = SarrusDet( D[1], M[1], M[2] ) / det;
522         f->brushprimit_texdef.coords[1][1] = SarrusDet( M[0], D[1], M[2] ) / det;
523         f->brushprimit_texdef.coords[1][2] = SarrusDet( M[0], M[1], D[1] ) / det;
524 }
525
526 // texture locking
527 // called before the points on the face are actually rotated
528 void RotateFaceTexture_BrushPrimit(face_t *f, int nAxis, float fDeg, vec3_t vOrigin )
529 {
530         // this is a placeholder to call the general texture locking algorithm
531         txlock_bRotation = true;
532         txl_nAxis = nAxis;
533         txl_fDeg = fDeg;
534         VectorCopy(vOrigin, txl_vOrigin);
535         TextureLockTransformation_BrushPrimit(f);
536 }
537
538 // compute the new brush primit texture matrix for a transformation matrix and a flip order flag (change plane orientation)
539 // this matches the select_matrix algo used in select.cpp
540 // this needs to be called on the face BEFORE any geometric transformation
541 // it will compute the texture matrix that will represent the same texture on the face after the geometric transformation is done
542 void ApplyMatrix_BrushPrimit(face_t *f, vec3_t matrix[3], vec3_t origin)
543 {
544   // this is a placeholder to call the general texture locking algorithm
545   txlock_bRotation = false;
546   VectorCopy(matrix[0], txl_matrix[0]);
547   VectorCopy(matrix[1], txl_matrix[1]);
548   VectorCopy(matrix[2], txl_matrix[2]);
549   VectorCopy(origin, txl_origin);
550   TextureLockTransformation_BrushPrimit(f);
551 }
552
553 // don't do C==A!
554 void BPMatMul(vec_t A[2][3], vec_t B[2][3], vec_t C[2][3])
555 {
556   C[0][0] = A[0][0]*B[0][0]+A[0][1]*B[1][0];
557   C[1][0] = A[1][0]*B[0][0]+A[1][1]*B[1][0];
558   C[0][1] = A[0][0]*B[0][1]+A[0][1]*B[1][1];
559   C[1][1] = A[1][0]*B[0][1]+A[1][1]*B[1][1];
560   C[0][2] = A[0][0]*B[0][2]+A[0][1]*B[1][2]+A[0][2];
561   C[1][2] = A[1][0]*B[0][2]+A[1][1]*B[1][2]+A[1][2];
562 }
563
564 void BPMatDump(vec_t A[2][3])
565 {
566   Sys_Printf("%g %g %g\n%g %g %g\n0 0 1\n", A[0][0], A[0][1], A[0][2], A[1][0], A[1][1], A[1][2]);
567 }
568
569 void BPMatRotate(vec_t A[2][3], float theta)
570 {
571   vec_t m[2][3];
572   vec_t aux[2][3];
573   memset(&m, 0, sizeof(vec_t)*6);
574   m[0][0] = cos(theta*Q_PI/180.0);
575   m[0][1] = -sin(theta*Q_PI/180.0);
576   m[1][0] = -m[0][1];
577   m[1][1] = m[0][0];
578   BPMatMul(A, m, aux);
579   BPMatCopy(aux,A);
580 }
581
582 // get the relative axes of the current texturing
583 void BrushPrimit_GetRelativeAxes(face_t *f, vec3_t vecS, vec3_t vecT)
584 {
585   vec_t vS[2],vT[2];
586   // first we compute them as expressed in plane axis base
587   // BP matrix has coordinates of plane axis base expressed in geometric axis base
588   // so we use the line vectors
589   vS[0] = f->brushprimit_texdef.coords[0][0];
590   vS[1] = f->brushprimit_texdef.coords[0][1];
591   vT[0] = f->brushprimit_texdef.coords[1][0];
592   vT[1] = f->brushprimit_texdef.coords[1][1];
593   // now compute those vectors in geometric space
594   vec3_t texS, texT; // axis base of the plane (geometric)
595   ComputeAxisBase(f->plane.normal, texS, texT);
596   // vecS[] = vS[0].texS[] + vS[1].texT[]
597   // vecT[] = vT[0].texS[] + vT[1].texT[]
598   vecS[0] = vS[0]*texS[0] + vS[1]*texT[0];
599   vecS[1] = vS[0]*texS[1] + vS[1]*texT[1];
600   vecS[2] = vS[0]*texS[2] + vS[1]*texT[2];
601   vecT[0] = vT[0]*texS[0] + vT[1]*texT[0];
602   vecT[1] = vT[0]*texS[1] + vT[1]*texT[1];
603   vecT[2] = vT[0]*texS[2] + vT[1]*texT[2];
604 }
605
606 // GL matrix 4x4 product (3D homogeneous matrix)
607 // NOTE: the crappy thing is that GL doesn't follow the standard convention [line][column]
608 //   otherwise it's all good
609 void GLMatMul(vec_t M[4][4], vec_t A[4], vec_t B[4])
610 {
611   unsigned short i,j;
612   for (i=0;i<4;i++)
613   {
614     B[i] = 0.0;
615     for (j=0;j<4;j++)
616     {
617       B[i] += M[j][i]*A[j];
618     }
619   }
620 }
621
622 qboolean IsBrushPrimitMode()
623 {
624         return(g_qeglobals.m_bBrushPrimitMode);
625 }