NeoPZ
tpzintrulet.cpp
Go to the documentation of this file.
1 
6 #include "tpzintrulet.h"
7 #include "pzerror.h"
8 #include "pzvec.h"
9 
11  // Checking argument (polinomial order to integrate exactly)
12  if(order < 0 || order > NRULESTRIANGLE_ORDER) {
13  PZError << "TPZGaussRule creation precision = " << order << " not available\n";
14  order = NRULESTRIANGLE_ORDER;
15  PZError << "TPZGaussRule creation precision gotten = " << order << "\n";
16  }
17 
19 }
20 
24  fWeight.Resize(0);
25  fNumInt = 0;
26 }
27 
28 //***************************************
29 //***************************************
30 void TPZIntRuleT::Loc(int i, TPZVec<REAL> &Points) const {
31  if(i>=0 && i<fNumInt){
32  Points[0] = fLocationKsi[i];
33  Points[1] = fLocationEta[i];
34  return;
35  }
36  else {
37  PZError << "ERROR(TPZIntRuleT::loc) Out of bounds!!\n";
38  }
39 }
40 
41 //***************************************
42 //***************************************
43 REAL TPZIntRuleT::W(int i) const {
44  if (i>=0 && i<fNumInt)
45  return fWeight[i];
46  else {
47  PZError << "ERROR(TPZGaussRule::w) Out of bounds!!\n";
48  return 0.0;
49  }
50 }
51 
66 #ifdef Length
67 # undef Length
68 #endif
69 #define Length(wts) (sizeof(wts) / (sizeof(wts[0])))
70 
71 #define Perm3(a) a, a, a
72 #define Dup3(w) (0.5L*w)
73 #define Perm21(a) a, a, 1.L - 2.0L*a, a, 1.L- 2.L*a, a, 1.L- 2.L*a, a, a
74 #define Dup21(w) Dup3(w), Dup3(w), Dup3(w)
75 #define Perm111(a,b) a, b, 1.L - a - b, a, 1.L - a - b, b, b, a , 1.L - a - b, \
76  b, 1.L - a - b, a, 1.L - a - b, a, b, 1.L - a - b, b, a
77 #define Dup111(w) Dup3(w), Dup3(w), Dup3(w), Dup3(w), Dup3(w), Dup3(w)
78 
79 long double QUAD_TRI_P1_wts[] = {
80  Dup3(1.L)
81 };
82 long double QUAD_TRI_P1_pts[Length(QUAD_TRI_P1_wts) * 3] = {
83  Perm3(1.L/3.L)
84 };
85 
86 long double QUAD_TRI_P2_wts[] = {
87  Dup21(1.L/3.L)
88 };
89 long double QUAD_TRI_P2_pts[Length(QUAD_TRI_P2_wts) * 3] = {
90  Perm21(1.L/6.L)
91 };
92 
93 long double QUAD_TRI_P3_wts[] = {
94  Dup21(.28114980244097964825351432270207695L),
95  Dup21(.05218353089235368507981901063125638L)
96 };
97 long double QUAD_TRI_P3_pts[Length(QUAD_TRI_P3_wts) * 3] = {
98  Perm21(.16288285039589191090016180418490635L),
99  Perm21(.47791988356756370000000000000000000L)
100 };
101 
102 long double QUAD_TRI_P4_wts[] = {
103  /* (620 + sqrt(213125 - 53320 * sqrt(10))) / 3720 */
104  Dup21(.22338158967801146569500700843312280L),
105  /* (620 - sqrt(213125 - 53320 * sqrt(10))) / 3720 */
106  Dup21(.10995174365532186763832632490021053L)
107 };
109  /* (8 - sqrt(10) + sqrt(38 - 44 * sqrt(2 / 5))) / 18 */
110  Perm21(.44594849091596488631832925388305199L),
111  /* (8 - sqrt(10) - sqrt(38 - 44 * sqrt(2 / 5))) / 18 */
112  Perm21(.09157621350977074345957146340220151L)
113 };
114 
115 long double QUAD_TRI_P5_wts[] = {
116  /* (155 - sqrt(15)) / 1200 */
117  Dup21(.12593918054482715259568394550018133L),
118  /* (155 + sqrt(15)) / 1200 */
119  Dup21(.13239415278850618073764938783315200L),
120  Dup3(9.L/40.L)
121 };
123  /* (6 - sqrt(15)) / 21 */
124  Perm21(.10128650732345633880098736191512383L),
125  /* (6 + sqrt(15)) / 21 */
126  Perm21(.47014206410511508977044120951344760L),
127  /* 1 / 3 */
128  Perm3(1.L/3.L)
129 };
130 
131 
132 /* Note: an 11-point rule has been found in:
133  * Day, David M., Mark A. Taylor, "A new 11 point degree 6 cubature
134  * formula for the triangle [Proceedings of the ICIAM 2007],"
135  * Journal Article, Proceedings of Applied Mathematics and Mechanics,
136  * Accepted/Published January 2008. */
137 long double QUAD_TRI_P6_wts[] = {
138  Dup21(.05084490637020681692093680910686898L),
139  Dup21(.11678627572637936602528961138557944L),
140  Dup111(.08285107561837357519355345642044245L)
141 };
143  Perm21(.06308901449150222834033160287081916L),
144  Perm21(.24928674517091042129163855310701908L),
145  Perm111(.05314504984481694735324967163139815L,
146  .31035245103378440541660773395655215L)
147 };
148 
149 long double QUAD_TRI_P7_wts[] = {
150  Dup21(.01353386251566556156682309245259393L),
151  Dup21(.07895125443201098137652145029770332L),
152  Dup21(.12860792781890607455665553308952344L),
153  Dup111(.05612014428337535791666662874675632L)
154 };
156  Perm21(.02826392415607634022359600691324002L),
157  Perm21(.47431132326722257527522522793181654L),
158  Perm21(.24114332584984881025414351267036207L),
159  Perm111(.76122274802452380000000000000000000L,
160  .04627087779880891064092559391702049L)
161 };
162 
163 long double QUAD_TRI_P8_wts[] = {
164  Dup3(.14431560767778716825109111048906462L),
165  Dup21(.10321737053471825028179155029212903L),
166  Dup21(.03245849762319808031092592834178060L),
167  Dup21(.09509163426728462479389610438858432L),
168  Dup111(.02723031417443499426484469007390892L)
169 };
171  Perm3(.33333333333333333333333333333333333L),
172  Perm21(.17056930775176020662229350149146450L),
173  Perm21(.05054722831703097545842355059659895L),
174  Perm21(.45929258829272315602881551449416932L),
175  Perm111(.26311282963463811342178578628464359L,
176  .00839477740995760533721383453929445L)
177 };
178 
179 long double QUAD_TRI_P9_wts[] = {
180  Dup3(.09713579628279883381924198250728863L),
181  Dup21(.03133470022713907053685483128720932L),
182  Dup21(.02557767565869803126167879855899982L),
183  Dup21(.07782754100477427931673935629940396L),
184  Dup21(.07964773892721025303289177426404527L),
185  Dup111(.04328353937728937728937728937728938L)
186 };
188  Perm3(.33333333333333333333333333333333333L),
189  Perm21(.48968251919873762778370692483619280L),
190  Perm21(.04472951339445270986510658996627636L),
191  Perm21(.43708959149293663726993036443535497L),
192  Perm21(.18820353561903273024096128046733557L),
193  Perm111(.74119859878449802069007987352342383L,
194  .22196298916076569567510252769319107L)
195 };
196 
197 long double QUAD_TRI_P10_wts[] = {
198  Dup3(.08093742879762288025711312381650193L),
199  Dup21(.07729858800296312168250698238034344L),
200  Dup21(.07845763861237173136809392083439673L),
201  Dup21(.01746916799592948691760716329067815L),
202  Dup21(.00429237418483282803048040209013191L),
203  Dup111(.03746885821046764297902076548504452L),
204  Dup111(.02694935259187995964544947958109671L)
205 };
207  Perm3(.33333333333333333333333333333333333L),
208  Perm21(.42727317884677553809044271751544715L),
209  Perm21(.18309922244867502052157438485022004L),
210  Perm21(.49043401970113058745397122237684843L),
211  Perm21(.01257244555158053273132908502104126L),
212  Perm111(.65426866792006614066657009558762790L,
213  .30804600168524770000000000000000000L),
214  Perm111(.12280457706855927343012981748128116L,
215  .03337183373930478624081644177478038L)
216 };
217 
218 long double QUAD_TRI_P11_wts[] = {
219  Dup3(.08117796029686715951547596874982357L),
220  Dup21(.01232404350690949411847390101623284L),
221  Dup21(.06282800974441010728333942816029398L),
222  Dup21(.01222037904936452975521221500393789L),
223  Dup21(.06770134895281150992098886182322559L),
224  Dup21(.04021969362885169042356688960756866L),
225  Dup111(.01476227271771610133629306558778206L),
226  Dup111(.04072799645829903966033695848161786L)
227 };
229  Perm3(.33333333333333333333333333333333333L),
230  Perm21(.03093835524543078489519501499130475L),
231  Perm21(.43649818113412884191761527655997324L),
232  Perm21(.49898476370259326628798698383139087L),
233  Perm21(.21468819795859433660687581387825086L),
234  Perm21(.11368310404211339020529315622836178L),
235  Perm111(.82561876616486290435880620030835800L,
236  .15974230459185018980086078822500751L),
237  Perm111(.64047231013486526767703659081896681L,
238  .31178371570959900000000000000000000L)
239 };
240 
241 long double QUAD_TRI_P12_wts[] = {
242  Dup21(.00616626105155901723386648378523035L),
243  Dup21(.06285822421788510035427051309288255L),
244  Dup21(.03479611293070894298932839729499937L),
245  Dup21(.04369254453803840213545726255747497L),
246  Dup21(.02573106644045533541779092307156443L),
247  Dup111(.02235677320230344571183907670231999L),
248  Dup111(.01731623110865889237164210081103407L),
249  Dup111(.04037155776638092951782869925223677L)
250 };
252  Perm21(.02131735045321037024685697551572825L),
253  Perm21(.27121038501211592234595134039689474L),
254  Perm21(.12757614554158592467389632515428357L),
255  Perm21(.43972439229446027297973662348436108L),
256  Perm21(.48821738977380488256466206525881104L),
257  Perm111(.69583608678780342214163552323607254L,
258  .28132558098993954824813069297455275L),
259  Perm111(.85801403354407263059053661662617818L,
260  .11625191590759714124135414784260182L),
261  Perm111(.60894323577978780685619243776371007L,
262  .27571326968551419397479634607976398L)
263 };
264 
265 long double QUAD_TRI_P13_wts[] = {
266  Dup3(.06796003658683164428177442468088488L),
267  Dup21(.05560196753045332870725746601046147L),
268  Dup21(.05827848511919998140476708351333981L),
269  Dup21(.00605233710353917184179280003229082L),
270  Dup21(.02399440192889473077371079945095965L),
271  Dup111(.03464127614084837046598682851091822L),
272  Dup111(.01496540110516566726324585713290344L),
273  Dup111(.02417903981159381913744574557306076L),
274  Dup111(.00959068100354326272259509016611089L)
275 };
277  Perm3(.33333333333333333333333333333333333L),
278  Perm21(.42694141425980040602081253503137421L),
279  Perm21(.22137228629183290065481255470507908L),
280  Perm21(.02150968110884318386929131353405208L),
281  Perm21(.48907694645253934990068971909020439L),
282  Perm111(.62354599555367557081585435318623659L,
283  .30844176089211777465847185254124531L),
284  Perm111(.86470777029544277530254595089569318L,
285  .11092204280346339541286954522167452L),
286  Perm111(.74850711589995219517301859578870965L,
287  .16359740106785048023388790171095725L),
288  Perm111(.72235779312418796526062013230478405L,
289  .27251581777342966618005046435408685L)
290 };
291 
292 long double QUAD_TRI_P14_wts[] = {
293  Dup3(.05859628522602859412789380634775601L),
294  Dup21(.00173515122972526756806186388080941L),
295  Dup21(.02616378255861452177782885918197827L),
296  Dup21(.00391972924240182909652082757014540L),
297  Dup21(.01224735975694086609728698992625048L),
298  Dup21(.02819962850325796010736630715156571L),
299  Dup21(.05088708718595948529603482754545404L),
300  Dup21(.05045343990160359919102089713411889L),
301  Dup111(.01706364421223345129002539938494722L),
302  Dup111(.00968346642550660040752096309341938L),
303  Dup111(.03638575592848500562201132776427165L),
304  Dup111(.00696466337351841242539972250424131L)
305 };
307  Perm3(.33333333333333333333333333333333333L),
308  Perm21(.00997976080645843241529352958205243L),
309  Perm21(.47997789352118838981055286508838991L),
310  Perm21(.15381195917696690000000000000000000L),
311  Perm21(.07402347711698781000000000000000000L),
312  Perm21(.13035468250333000000000000000000000L),
313  Perm21(.23061722602665313429960537009838312L),
314  Perm21(.42233208341914782411440871379139388L),
315  Perm111(.78623738593466100332962211403309001L,
316  .19061636003190090424614328286530343L),
317  Perm111(.63055214366060744162240907556881292L,
318  .36232313774354714461832673435977294L),
319  Perm111(.62657732985630631423351231375342650L,
320  .29077120588366741502481681748167319L),
321  Perm111(.91420998492962541223996709938504695L,
322  .07116571087775076254759245029243364L)
323 };
324 
325 long double QUAD_TRI_P15_wts[] = {
326  Dup3(.04403871087843427985301732721493388L),
327  Dup21(.04618478718202697994871566760191669L),
328  Dup21(.00649890661733271652688280349281019L),
329  Dup21(.01799361425265840324466992416715655L),
330  Dup21(.04177310503914135411968606056414597L),
331  Dup21(.00305954760911646654843016992834484L),
332  Dup21(.00201243505255864734409031875654046L),
333  Dup21(.01677561093050912232611145688795876L),
334  Dup111(.01546074918971427486608803040924742L),
335  Dup111(.02849989033954742339273955875330195L),
336  Dup111(.03209435048348959564209923573709566L),
337  Dup111(.01150858163687071128402324377324186L),
338  Dup111(.00461430652896710314358717609185406L)
339 };
341  Perm3(.33333333333333333333333333333333333L),
342  Perm21(.22733221881914287420250436849229406L),
343  Perm21(.49716257743188742987380980001602329L),
344  Perm21(.47884973534895458333922920014385258L),
345  Perm21(.40498603909827199169724464234269204L),
346  Perm21(.01593121667174443211342773294126896L),
347  Perm21(.16558326242608140000000000000000000L),
348  Perm21(.07313360471922872772687381210732441L),
349  Perm111(.66526073307221393906236441338569119L,
350  .31635283934494723008633813095024529L),
351  Perm111(.71252198724254553304884901162338783L,
352  .09346075114991753000000000000000047L),
353  Perm111(.55964836223539321841224845401923000L,
354  .34422901758219320000000000000000160L),
355  Perm111(.81047659761907686304683273029057126L,
356  .17104724831425795154765033192558481L),
357  Perm111(.91607564403173118856460883877832000L,
358  .07305599647918648961294908192742498L)
359 };
360 
361 long double QUAD_TRI_P16_wts[] = {
362  Dup3(.04802218868037709055183940458051988L),
363  Dup21(.01470910030680192710340364286186919L),
364  Dup21(.02954458654931925599530972679646409L),
365  Dup21(.02612501735108837749859756549171557L),
366  Dup21(.00278038735239000697500301613866207L),
367  Dup21(.03182177300053664950342729005594961L),
368  Dup21(.00864583434950965990117373416984893L),
369  Dup111(.01430033290449536514661642536825213L),
370  Dup111(.02784977720360082995222987342395349L),
371  Dup111(.00704167340663609756237018808928069L),
372  Dup111(.01789983825993372860177020907581078L),
373  Dup111(.02745820038434976307247003810091720L),
374  Dup111(.00729979693943176208411254408777766L)
375 };
377  Perm3(.33333333333333333333333333333333333L),
378  Perm21(.08179498313137387264146559311886101L),
379  Perm21(.16530060196977965062676193293355656L),
380  Perm21(.46859210534946138669460289729660561L),
381  Perm21(.01443881344541668261410895669566020L),
382  Perm21(.24178428539178335340689445929320769L),
383  Perm21(.49531034298776996406549508687740551L),
384  Perm111(.65051340266135229943114468484168666L,
385  .33139974453708955658132316818259388L),
386  Perm111(.60401128149599703984940410303596702L,
387  .30324716274994218504155217807834692L),
388  Perm111(.80216825757474166361686194781166705L,
389  .18802805952123717344418211429398875L),
390  Perm111(.75650560644282839655115407575806082L,
391  .18350466852229686368238027743700035L),
392  Perm111(.46593843871411818488381073359154639L,
393  .35964594879750460000000000000001000L),
394  Perm111(.90639484399204150136249966186534000L,
395  .07719437129575543228251522505271386L)
396 };
397 
398 long double QUAD_TRI_P17_wts[] = {
399  Dup3(.04475687144434462937183647670425513L),
400  Dup21(.01736688502674779645049111764776038L),
401  Dup21(.03059934807610353272266564726895704L),
402  Dup21(.02858770857859978020704009121768920L),
403  Dup21(.00664743192975369323231849554546676L),
404  Dup21(.00747618940201851182224557347080098L),
405  Dup21(.02504998650383874531455895190550778L),
406  Dup111(.00147981089211964494480953682750477L),
407  Dup111(.00512113624674810606589435040573260L),
408  Dup111(.02731735936959280591853168984239567L),
409  Dup111(.01400572867590928159786633211401179L),
410  Dup111(.00780927569745836009810987323288001L),
411  Dup111(.01816572845979167217607207751722372L),
412  Dup111(.02744437399245832776208345541478450L)
413 };
415  Perm3(.33333333333333333333333333333333333L),
416  Perm21(.09569850886271093994316257860237634L),
417  Perm21(.17013863967877544672324723079568443L),
418  Perm21(.41802068586795497622263464239342782L),
419  Perm21(.49658148050662495497054035306227918L),
420  Perm21(.04166211482880764279207885159834192L),
421  Perm21(.46793290572942357826819008536171190L),
422  Perm111(.96953119890372205619454058305953242L,
423  .02892509162021824607152804771406821L),
424  Perm111(.75972438753862412955532719532266120L,
425  .23444175526356877454266053091297880L),
426  Perm111(.29549931696830150000000000000001000L,
427  .49591124666075357542303450004375516L),
428  Perm111(.62560638215769702707019209266693705L,
429  .35341769454149706762632499077099377L),
430  Perm111(.87217444723318479290318300141560742L,
431  .11272864181421976861888886768074196L),
432  Perm111(.74751231944000604006240678176087530L,
433  .19907027879785788131339143981558306L),
434  Perm111(.59886879088323805980616769726351095L,
435  .30358518307132607653202051204584937L)
436 };
437 
438 long double QUAD_TRI_P18_wts[] = {
439  Dup21(.01397786164528602097958400799055493L),
440  Dup21(.00055490697921321378506845551525090L),
441  Dup21(.02102681381970466902842986851624498L),
442  Dup21(.03401821217992769974722652741822109L),
443  Dup111(.02791016580477499514184347400781694L),
444  Dup111(.01821468612715086612673395662068577L),
445  Dup111(.01426702365810979307751982410955666L),
446  Dup111(.01423712309067505070431276377415596L),
447  Dup111(.01925758385467478779913738368202133L),
448  Dup111(.00970513228438064114878227633239023L),
449  Dup111(.00762978813433212899578245563385336L),
450  Dup111(.01061873913635034479446354367052828L),
451  Dup111(.00571066980327583881341421438268949L),
452  Dup111(.00432685746087641829452234473283270L)
453 };
455  Perm21(.07327088646438283157861967148768954L),
456  Perm21(.00391774898322823164278407441958060L),
457  Perm21(.46759731898871106165151299662296245L),
458  Perm21(.41791621096741131201212681051399350L),
459  Perm111(.16538169336028948005449026923917662L,
460  .56369670566087075380514589393807372L),
461  Perm111(.28750089440578398999619391313966060L,
462  .28604232613920474912095810748030295L),
463  Perm111(.12588931431982479601706483994903803L,
464  .69604321864246119579257486028195390L),
465  Perm111(.06322191594650261449357508011699804L,
466  .76054555188768243261459476379786871L),
467  Perm111(.07891022745402051775207221037548892L,
468  .59201963127175856332262057540222541L),
469  Perm111(.03805805350678571432611899159626213L,
470  .68368125963599985248012408745381310L),
471  Perm111(.01429035213045402564992411031307492L,
472  .85170403713705581502852165344276639L),
473  Perm111(.01296727234325317231234163433009032L,
474  .57473249288814902889945093868968971L),
475  Perm111(.00764859482084089933079262881822729L,
476  .73551044083072929870313522448164061L),
477  Perm111(.01271046057225546793114249181358220L,
478  .93934508764373178870740420268282255L)
479 };
480 
481 /* Note: the rule QUAD_TRI_P19 was taken from the book by
482  * P. Solin, K. Segeth, and I. Dolezel,
483  * "Higer-order Finite Element Methods",
484  * Chapman and Hall/CRC Press, 2003. */
485 long double QUAD_TRI_P19_wts[] = {
486  Dup3(.03290633138891865208361434484647497L),
487  Dup21(.01033073189127205336703996357174833L),
488  Dup21(.02238724726301639252918455603516271L),
489  Dup21(.03026612586946807086528019098259122L),
490  Dup21(.03049096780219778100003158657852042L),
491  Dup21(.02415921274164090491184803098664001L),
492  Dup21(.01605080358680087529162277027642948L),
493  Dup21(.00808458026178406048180567324219442L),
494  Dup21(.00207936202748478075134750167439841L),
495  Dup111(.00388487690498138975670499199277266L),
496  Dup111(.02557416061202190389292970195260027L),
497  Dup111(.00888090357333805774552592470351753L),
498  Dup111(.01612454676173139121978526932783766L),
499  Dup111(.00249194181749067544058464757594956L),
500  Dup111(.01824284011895057837766571320973615L),
501  Dup111(.01025856373619852130804807004235813L),
502  Dup111(.00379992885530191397907315371363970L)
503 };
505  Perm3(.33333333333333333333333333333333333L),
506  Perm21(.48960998707300633196613106574829817L),
507  Perm21(.45453689269789266204675939053572830L),
508  Perm21(.40141668064943118739399562381068860L),
509  Perm21(.25555165440309761132218176810926787L),
510  Perm21(.17707794215212955164267520651590115L),
511  Perm21(.11006105322795186130008495167737397L),
512  Perm21(.05552862425183967124867841247135571L),
513  Perm21(.01262186377722866849023476677870599L),
514  Perm111(.60063379479464500000000000000000000L,
515  .39575478735694286230479469406582787L),
516  Perm111(.13446675453077978561204319893264695L,
517  .55760326158878396836395324250118097L),
518  Perm111(.72098702581736505521665290233827892L,
519  .26456694840652020804030173490121494L),
520  Perm111(.59452706895587092461388928802650670L,
521  .35853935220595058842492699064590088L),
522  Perm111(.83933147368083857861749007714840520L,
523  .15780740596859474473767360335950651L),
524  Perm111(.22386142409791569130336938950653642L,
525  .70108797892617336732328833655951158L),
526  Perm111(.82293132406985663162747155916053316L,
527  .14242160111338343731557475687723745L),
528  Perm111(.92434425262078402945585913790156314L,
529  .06549462808293770339232652498592557L)
530 };
531 
532 long double QUAD_TRI_P20_wts[] = {
533  Dup3(.01253760799449665657358563677239480L),
534  Dup21(.02747186987642421374845354960735985L),
535  Dup21(.00976527227705142304136469142942368L),
536  Dup21(.00139841953539182352392336315978673L),
537  Dup21(.00929210262518518263042820340303303L),
538  Dup21(.01657787603236692532602362503518398L),
539  Dup111(.02066776234866507696142197001297288L),
540  Dup111(.02082223552115450730687855619932975L),
541  Dup111(.00956863841984906068887584504583203L),
542  Dup111(.02445277096897246388564392070240889L),
543  Dup111(.00315573063063053400382640032072957L),
544  Dup111(.01213679636532129693701330908075738L),
545  Dup111(.01496648014388644903652491185157070L),
546  Dup111(.00632759332177773956932403275043979L),
547  Dup111(.00134256031206369588497985129814333L),
548  Dup111(.00277607691634755406772935615580153L),
549  Dup111(.01073984447418494155517344744795167L),
550  Dup111(.00536780573818745320524741002126972L)
551 };
553  Perm3(.33333333333333333333333333333333333L),
554  Perm21(.21587430593299197319025454384018276L),
555  Perm21(.07537676652974727809728543094591628L),
556  Perm21(.01030082813722179211368621600969694L),
557  Perm21(.49360221129870016551192083214505357L),
558  Perm21(.46155093810692529674104871029151803L),
559  Perm111(.32862140642423699330349746095091325L,
560  .42934057025821037521395880046639840L),
561  Perm111(.26048036178656875641959301708115346L,
562  .10157753428096944616875500619617966L),
563  Perm111(.13707423584645530000000000000000000L,
564  .71006597300113015998790407454640790L),
565  Perm111(.14672694587229978430416098848745303L,
566  .49854547767841484938962269670761193L),
567  Perm111(.02699897774255329000000000000000000L,
568  .04918672267258200161970371257758717L),
569  Perm111(.06187178593361702684171247001223384L,
570  .77966014654056939536035061907681080L),
571  Perm111(.04772436742762199620835268010429344L,
572  .37049153914954763692014962025673877L),
573  Perm111(.12060051518636437996723378704007933L,
574  .86334694875475264849798799609252174L),
575  Perm111(.00269714779670978767164891450128273L,
576  .05619493818774550298789230198658868L),
577  Perm111(.00301563327794236265727625982347101L,
578  .20867500674842135095759446306135771L),
579  Perm111(.02990537578845701880692877386433865L,
580  .72115124091203409102810415020509411L),
581  Perm111(.00675665422246098853994581751922784L,
582  .64005544194054188990405366827216467L)
583 };
584 
585 long double QUAD_TRI_P21_wts[] = {
586  Dup3(.02756225695287648096690704482451431L),
587  Dup21(.02206021541348850119135073403311636L),
588  Dup21(.02346001593867148849301344495230002L),
589  Dup21(.00032688959504719054621455750154654L),
590  Dup21(.00326531946293996823433530409586668L),
591  Dup21(.01175646291541279770430796921338205L),
592  Dup21(.01178076841991151684555757909867614L),
593  Dup111(.00226881081880114080533570433430431L),
594  Dup111(.00259601096443632006067378366548822L),
595  Dup111(.00463452978587186021234789056159687L),
596  Dup111(.00479433605454885793485744871991192L),
597  Dup111(.00571247883672361156725063834296336L),
598  Dup111(.00586582760432212163695579870000227L),
599  Dup111(.00941376305909158758981826852034708L),
600  Dup111(.01341494379665642491002202661089309L),
601  Dup111(.01571691809208324594350000113784617L),
602  Dup111(.01686368301443690459165096388619991L),
603  Dup111(.02139002708532009837783229808035898L),
604  Dup111(.02307679218949268136788087552189154L)
605 };
607  Perm3(.33333333333333333333333333333333333L),
608  Perm21(.20093527706508527987296185156416367L),
609  Perm21(.43765916596192717973183384418805413L),
610  Perm21(.00343395649059617685095991220960492L),
611  Perm21(.04664348477530675349517624043214192L),
612  Perm21(.38642225176307149094035202416772642L),
613  Perm21(.09543547110853091010857168104147605L),
614  Perm111(.95551380335045636050131472514677118L,
615  .03571862787316335823804160897543867L),
616  Perm111(.88663881342886822612490057469143760L,
617  .10814322491564621152738861104631270L),
618  Perm111(.78426284588043415429664399039819537L,
619  .20746444959987645682438042951572740L),
620  Perm111(.88292395505020003271134898731688967L,
621  .08568470872031694000000000000001000L),
622  Perm111(.66899196444107724049132248320989459L,
623  .32149400301428881688168321268348603L),
624  Perm111(.55207212103556096415716096525277878L,
625  .43794221879334138355236807696291701L),
626  Perm111(.79759296559656856762931422329572582L,
627  .16191645306357785675100677020385905L),
628  Perm111(.67751471511977148463499116634413256L,
629  .27450476740199490385900297290733317L),
630  Perm111(.54299741558909160533113611683919342L,
631  .40533599807500692794989089537632556L),
632  Perm111(.70545990556996856165885634154060172L,
633  .18773768065643534277281674394512005L),
634  Perm111(.57480057306650846221598245054985001L,
635  .30569683476605516651279255664984316L),
636  Perm111(.47177880850461481660397704013492420L,
637  .31214446687089088167080460581557645L)
638 };
639 
641  if(order > 21) order = 21;
642  int NRGAUPO[22] = {1, 1, 3, 6, 6, 7, 12, 15, 16, 19, 25, 28, 33, 37, 46, 52, 55, 61, 72, 73, 88, 91};
643  fNumInt = NRGAUPO[order];
646  fWeight.Resize(fNumInt,0.0L);
647 
648  switch(order) {
649  case 0:
650  case 1:
652  break;
653  case 2:
655  break;
656  case 3:
658  break;
659  case 4:
661  break;
662  case 5:
664  break;
665  case 6:
667  break;
668  case 7:
670  break;
671  case 8:
673  break;
674  case 9:
676  break;
677  case 10:
679  break;
680  case 11:
682  break;
683  case 12:
685  break;
686  case 13:
688  break;
689  case 14:
691  break;
692  case 15:
694  break;
695  case 16:
697  break;
698  case 17:
700  break;
701  case 18:
703  break;
704  case 19:
706  break;
707  case 20:
709  break;
710  case 21:
712  break;
713  default:
714  PZError << "TPZIntRuleT not implemented by order " << order << std::endl;
715  }
716  return order;
717 }
718 
719 void TPZIntRuleT::TransformBarycentricCoordInCartesianCoord(long double baryvec[],long double weightvec[]) {
720  for(int i=0;i<fNumInt;i++) {
721  fWeight[i] = weightvec[i];
722  fLocationKsi[i] = baryvec[3*i+1];
723  fLocationEta[i] = baryvec[3*i+2];
724  }
725 }
726 
long double QUAD_TRI_P5_pts[Length(QUAD_TRI_P5_wts) *3]
long double QUAD_TRI_P3_pts[Length(QUAD_TRI_P3_wts) *3]
Definition: tpzintrulet.cpp:97
long double QUAD_TRI_P16_pts[Length(QUAD_TRI_P16_wts) *3]
long double QUAD_TRI_P15_wts[]
long double QUAD_TRI_P6_pts[Length(QUAD_TRI_P6_wts) *3]
long double QUAD_TRI_P10_wts[]
long double QUAD_TRI_P15_pts[Length(QUAD_TRI_P15_wts) *3]
REAL W(int i) const
Return weight for the ith point.
Definition: tpzintrulet.cpp:43
long double QUAD_TRI_P20_wts[]
int fNumInt
Number of integration points for this object.
Definition: tpzintrulet.h:24
long double QUAD_TRI_P6_wts[]
long double QUAD_TRI_P20_pts[Length(QUAD_TRI_P20_wts) *3]
long double QUAD_TRI_P18_wts[]
int ComputingSymmetricCubatureRule(int order)
Computes the cubature rules following the symmetric construction presented at Linbo Zhang article...
Contains the TPZIntRuleT class which defines integration rule for triangles based on Linbo Zhang&#39;s pa...
Templated vector implementation.
long double QUAD_TRI_P21_pts[Length(QUAD_TRI_P21_wts) *3]
TPZManVector< long double > fLocationKsi
Location of the integration point Ksi.
Definition: tpzintrulet.h:26
#define Dup111(w)
Definition: tpzintrulet.cpp:77
Defines PZError.
long double QUAD_TRI_P12_wts[]
TPZManVector< long double > fLocationEta
Location of the integration point Eta.
Definition: tpzintrulet.h:28
long double QUAD_TRI_P12_pts[Length(QUAD_TRI_P12_wts) *3]
#define Dup21(w)
Definition: tpzintrulet.cpp:74
TPZManVector< long double > fWeight
Weight of the integration point.
Definition: tpzintrulet.h:30
long double QUAD_TRI_P18_pts[Length(QUAD_TRI_P18_wts) *3]
virtual void Resize(const int64_t newsize, const T &object)
Resizes the vector object.
Definition: pzmanvector.h:426
int fOrder
the polynomial order this integration rule can integrate
Definition: tpzintrulet.h:32
#define Dup3(w)
Definition: tpzintrulet.cpp:72
long double QUAD_TRI_P10_pts[Length(QUAD_TRI_P10_wts) *3]
long double QUAD_TRI_P21_wts[]
long double QUAD_TRI_P2_wts[]
Definition: tpzintrulet.cpp:86
long double QUAD_TRI_P19_pts[Length(QUAD_TRI_P19_wts) *3]
void Loc(int i, TPZVec< REAL > &pos) const
Returns location of the ith point.
Definition: tpzintrulet.cpp:30
long double QUAD_TRI_P7_wts[]
void TransformBarycentricCoordInCartesianCoord(long double baryvec[], long double weightvec[])
Transforms barycentric coordinates (3 component) of the point in triange in cartesian coordinates (2 ...
long double QUAD_TRI_P9_pts[Length(QUAD_TRI_P9_wts) *3]
long double QUAD_TRI_P4_pts[Length(QUAD_TRI_P4_wts) *3]
long double QUAD_TRI_P3_wts[]
Definition: tpzintrulet.cpp:93
#define Perm21(a)
Definition: tpzintrulet.cpp:73
long double QUAD_TRI_P5_wts[]
long double QUAD_TRI_P17_wts[]
~TPZIntRuleT()
Default destructor.
Definition: tpzintrulet.cpp:21
long double QUAD_TRI_P13_wts[]
long double QUAD_TRI_P11_wts[]
long double QUAD_TRI_P2_pts[Length(QUAD_TRI_P2_wts) *3]
Definition: tpzintrulet.cpp:89
TPZIntRuleT(int order)
Constructor of integration rule for triangle.
Definition: tpzintrulet.cpp:10
long double QUAD_TRI_P19_wts[]
#define Perm111(a, b)
Definition: tpzintrulet.cpp:75
long double QUAD_TRI_P11_pts[Length(QUAD_TRI_P11_wts) *3]
long double QUAD_TRI_P16_wts[]
#define Length(wts)
Definition: tpzintrulet.cpp:69
long double QUAD_TRI_P13_pts[Length(QUAD_TRI_P13_wts) *3]
long double QUAD_TRI_P1_pts[Length(QUAD_TRI_P1_wts) *3]
Definition: tpzintrulet.cpp:82
long double QUAD_TRI_P8_pts[Length(QUAD_TRI_P8_wts) *3]
long double QUAD_TRI_P14_pts[Length(QUAD_TRI_P14_wts) *3]
long double QUAD_TRI_P14_wts[]
long double QUAD_TRI_P17_pts[Length(QUAD_TRI_P17_wts) *3]
long double QUAD_TRI_P1_wts[]
Definition: tpzintrulet.cpp:79
long double QUAD_TRI_P9_wts[]
long double QUAD_TRI_P8_wts[]
long double QUAD_TRI_P4_wts[]
#define PZError
Defines the output device to error messages and the DebugStop() function.
Definition: pzerror.h:15
long double QUAD_TRI_P7_pts[Length(QUAD_TRI_P7_wts) *3]
#define Perm3(a)
Definition: tpzintrulet.cpp:71