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