37 1 NEL , MATB, C10, C01, C20,
38 2 C11 ,C02, C30, C21, C12,
39 3 C03 ,D1 ,D2 , D3, SIG,
40 4 BI1,BI2,JDET ,FLAG_MUL,
41 5 NVARF,COEFR, BETAF,COEFM ,
46#include "implicit_f.inc"
50 INTEGER,
INTENT(IN) :: NEL,FLAG_MUL,NVARF,IFORM
51 my_real,
INTENT(IN) :: C10,C01,C20,C11,C02,C30,C21,C12,C03,
55 my_real,
DIMENSION(NEL, 3,3),
INTENT(IN) :: MATB(NEL,3,3)
59 my_real,
DIMENSION(NEL),
INTENT(OUT) :: bi1,bi2,jdet
60 my_real,
DIMENSION(NEL, 3,3),
INTENT(OUT) :: sig
64 my_real,
DIMENSION(NEL,NVARF),
INTENT(INOUT) :: uvarf
71 . wmax,lpchain(nel), trace(nel),traceb(nel),j2third(nel),
72 . sb1(nel), sb2(nel),sb3(nel),tbnorm(nel),dgamma(nel),i1(nel),
73 . aa,bb,cc,trb2,trb22,rbulk,
74 . i2(nel),jthird(nel),j4third(nel),eta(nel),ww(nel) ,
75 . dphidi1(nel) ,dphidi2(nel) , dphidj(nel) ,inv2j(nel),
80 CALL prodmat (matb , matb, matb2, nel)
83 jdet(i)=matb(i,1,1)*matb(i,2,2)*matb(i,3,3)-matb(i,1,1)*matb(i,2,3)*matb(i,3,2) -
84 . matb(i,3,3)*matb(i,1,2)*matb(i,2,1) +matb(i,1,2)*matb(i,2,3)*matb(i
85 . matb(i,2,1)*matb(i,3,2)*matb(i,1,3) -matb(i,2,2)*matb(i,3,1)*matb(i,1,3)
88 i1(i) = matb(i,1,1)+matb(i,2,2)+matb(i,3,3)
91 trb22= matb2(i,1,1) + matb2(i,2,2) +matb2(i,3,3)
94 i2(i)= (trb2 - trb22)/two
97 jthird(i) = exp((-third )*log(jdet(i)))
98 j2third(i) = jthird(i)**2
99 j4third(i) = jthird(i)**4
109 bi1(i) = i1(i) * j2third(i)
111 bi2(i) = i2(i)*j4third(i)
116 ww(i) = c10 *(bi1(i)-three) + c20 *(bi1(i)-three)**2 + c30 *(bi1(i)-three)**3
117 . + c01 *(bi2(i)-three) + c02 *(bi2(i)-three)**2 + c03 *(bi2(i)-three)**3
118 . + c11 *(bi1(i)-three)*(bi2(i)-three)
119 . + c12 *(bi1(i)-three)*(bi2(i)-three)**2
120 . + c21 *(bi2(i)-three)*(bi1(i)-three)**2
121 wmax =
max(wmax, ww(i))
126 !====================================
127 IF(flag_mul == 1)
THEN
129 1 nel ,nvarf, coefr,betaf ,
130 2 coefm, ww , uvarf,eta )
135 eta(i) =
max(
min(eta(i),one),em20)
137 dphidi1(i) = eta(i)*(c10 + two *c20 *(bi1(i)-three)+ three*c30 *(bi1(i)-three)**2
138 . + c11 *(bi2(i)-three)+ c12 *(bi2(i)-three)**2
139 . + two *c21 *(bi1(i)-three)*(bi2(i)-three))
141 dphidi2(i) = eta(i)*(c01 + two*c02*(bi2(i)-three) +three*c03*(bi2(i)-three)**2
142 . + c11*(bi1(i)-three) + c21*(bi1(i)-three)**2
143 . + two*c12*(bi1(i)-three)*(bi2(i)-three))
145 inv2j(i)=two/
max(em20,jdet(i))
149 dphidj(i) = two*d1* (jdet(i)-one) + four * d2 * (jdet(i)-one)**3 + six*d3*(jdet(i)-one)**5
151 ELSEIF (iform == 2)
THEN
153 dphidj(i) = rbulk * (one - one / jdet(i))
160 aa = (dphidi1(i) + dphidi2(i) * bi1(i))*inv2j(i)*j2third(i)
161 bb = dphidi2(i) *inv2j(i)*j4third(i)
162 cc = third* inv2j(i)* ( bi1(i)* dphidi1(i)+two* bi2(i)*dphidi2(i))
164 sig(i,1,1) = aa*matb(i,1,1)
168 sig(i,2,2) = aa*matb(i,2,2)
172 sig(i,3,3) = aa*matb(i,3,3)
176 sig(i,1,2) = aa*matb(i,1,2)
178 sig(i,2,3) = aa*matb(i,2,3)
180 sig(i,3,1) = aa*matb(i,3,1)
182 sig(i,2,1)=sig(i,1,2)
183 sig(i,3,2)=sig(i,2,3)
184 sig(i,1,3)=sig(i,3,1)
198 1 NEL , MATB, C10, C01, C20,
199 2 C11 ,C02, C30, C21, C12,
200 3 C03 ,D1 ,D2 , D3, SIG,
201 4 BI1,BI2,JDET ,FLAG_MUL,
202 5 NVARF,COEFR, BETAF,COEFM ,
203 6 UVARF,CII ,RBULK,IFORM)
207#include "implicit_f.inc"
211 INTEGER,
INTENT(IN) :: NEL,FLAG_MUL,NVARF,IFORM
212 my_real,
INTENT(IN) :: C10,C01,C20,C11,C02,C30,C21,C12,C03,
214 . COEFR, BETAF,COEFM ,RBULK
216 my_real,
DIMENSION(NEL, 3,3),
INTENT(IN) :: MATB(NEL,3,3)
220 my_real,
DIMENSION(NEL),
INTENT(OUT) :: BI1,BI2,JDET
221 my_real,
DIMENSION(NEL, 3,3),
INTENT(OUT) :: SIG
222 my_real,
DIMENSION(NEL, 3),
INTENT(OUT) :: CII
226 my_real,
DIMENSION(NEL,NVARF),
INTENT(INOUT) :: uvarf
233 . wmax,lpchain(nel), trace(nel),traceb(nel),j2third(nel),matb2(nel,3,3),
234 . sb1(nel), sb2(nel),sb3(nel),tbnorm(nel),dgamma(nel),i1(nel),
235 . aa,bb,cc,trb2,trb22,
236 . i2(nel),jthird(nel),j4third(nel),eta(nel),ww(nel) ,
237 . dphidi1(nel) ,dphidi2(nel) , dphidj(nel) ,inv2j(nel),
238 . dphi2di1(nel) ,dphi2di2(nel) , dphi2dj(nel),lam_b(3),lam_b_1(3),
243 CALL prodmat (matb , matb, matb2, nel)
247 jdet(i)=matb(i,1,1)*matb(i,2,2)*matb(i,3,3)-matb(i,1,1)*matb
248 . matb(i,3,3)*matb(i,1,2)*matb(i,2,1) +matb(i,1,2)*matb(i,2,3)*matb(i,3,1) +
249 . matb(i,2,1)*matb(i,3,2)*matb(i,1,3) -matb(i,2,2)*matb(i,3,1
253 i1(i) = matb(i,1,1)+matb(i,2,2)+matb(i,3,3)
256 trb22= matb2(i,1,1) + matb2
258 i2(i)= (trb2 - trb22)/two
260 IF(jdet(i)>zero)
THEN
261 jthird(i) = exp((-third )*log(jdet(i)))
262 j2third(i) = jthird(i)**2
263 j4third(i) = jthird(i)**4
273 bi1(i) = i1(i) * j2third(i)
275 bi2(i) = i2(i)*j4third(i)
280 ww(i) = c10 *(bi1(i)-three) + c20 *(bi1(i)-three)**2 + c30 *(bi1(i)-three)**3
281 . + c01 *(bi2(i)-three) + c02 *(bi2(i)-three)**2 + c03 *(bi2(i)-three)**3
282 . + c11 *(bi1(i)-three)*(bi2(i)-three)
283 . + c12 *(bi1(i)-three)*(bi2(i)-three)**2
284 . + c21 *(bi2(i)-three)*(bi1(i)-three)**2
285 wmax =
max(wmax, ww(i))
291 IF(flag_mul == 1)
THEN
293 1 nel ,nvarf, coefr,betaf ,
294 2 coefm, ww , uvarf,eta )
299 eta(i) =
max(
min(eta(i),one),em20)
301 dphidi1(i) = eta(i)*(c10 + two *c20 *(bi1(i)-three)+ three*c30 *(bi1(i)-three)**2
302 . + c11 *(bi2(i)-three)+ c12 *(bi2(i)-three)**2
303 . + two *c21 *(bi1(i)-three)*(bi2(i)-three))
305 dphidi2(i) = eta(i)*(c01 + two*c02*(bi2(i)-three) +three*c03*(bi2(i)-three)**2
306 . + c11*(bi1(i)-three) + c21*(bi1(i)-three)**2
307 . + two*c12*(bi1(i)-three)*(bi2(i)-three))
308 inv2j(i)=two/
max(em20,jdet(i))
312 dphidj(i) = two*d1* (jdet(i)-one) + four * d2 * (jdet(i)-one)**3 + six*d3*(jdet(i)-one)**5
314 ELSEIF (iform == 2)
THEN
316 dphidj(i) = rbulk * (one - one / jdet(i))
322 aa = (dphidi1(i) + dphidi2(i) * bi1(i))*inv2j(i)*j2third(i)
323 bb = dphidi2(i) *inv2j(i)*j4third(i)
324 cc = third* inv2j(i)* ( bi1(i)* dphidi1(i)+two* bi2(i)*dphidi2(i))
326 sig(i,1,1) = aa*matb(i,1,1)
330 sig(i,2,2) = aa*matb(i,2,2)
334 sig(i,3,3) = aa*matb(i,3,3)
338 sig(i,1,2) = aa*matb(i,1,2)
340 sig(i,2,3) = aa*matb(i,2,3)
342 sig(i,3,1) = aa*matb(i,3,1)
344 sig(i,2,1)=sig(i,1,2)
345 sig(i,3,2)=sig(i,2,3)
346 sig(i,1,3)=sig(i,3,1)
352 dphi2dj(i) = two*d1 + twelve * d2 * (jdet(i)-one)**2 + thirty*d3*(jdet(i)-one)**4
354 ELSEIF (iform == 2)
THEN
356 dphi2dj(i) = rbulk/(jdet(i)**2)
360 dphi2di1(i) = two*eta(i)*(c20 + three*c30*(bi1(i)-three)+ c21*(bi2(i)-three))
362 dphi2di2(i) = two*eta(i)*(c02 +three*c03*(bi2(i)-three) + c12*(bi1(i)-three))
364 lam_b(1) = matb(i,1,1)*j2third(i)
365 lam_b(2) = matb(i,2,2)*j2third(i)
366 lam_b(3) = matb(i,3,3)*j2third(i)
367 lam_b_1(1:3) = one/lam_b(1:3)
370 cii(i,1:3) = two*(two_third*dphidi1(i)*(lam_b(1:3)+bi1_3)+dphi2di1(i)*(lam_b(1:3)-bi1_3)+
371 . two_third*dphidi2(i)*(lam_b_1(1:3)+bi2_3)+dphi2di2(i)*(lam_b_1
385 1 NEL ,EV,NUPARAM, UPARAM,T1,T2,T3,STIFF,
390#include "implicit_f.inc"
394 INTEGER NEL , NUPARAM
396 . EV(NEL,3),UPARAM(NUPARAM)
401 . t1(nel), t2(nel),t3(nel)
411 . lpchain(nel), trace(nel),traceb(nel),jdet(nel),stiff(nel),
412 . sb1(nel), sb2(nel),sb3(nel),tbnorm(nel),dgamma(nel),
413 . evpn(nel,3),evel(nel,3),evb(nel,3),
414 . aa,bb,cc,c10,c01,c20,c11,c02,c30,c21,c12,c03,d1,d2,d3,
415 . i2(nel),jthird(nel),j4third(nel),bi1(nel),
416 . bi2(nel),dphidi1(nel) ,dphidi2(nel) , dphidj(nel) ,inv2j(nel)
434 jdet(i) = ev(i,1)*ev(i,2)*ev(i,3)
436 i2(i)= ev(i,1)*ev(i,1)*ev(i,2)*ev(i,2)
437 . +ev(i,3)*ev(i,3)*ev(i,2)*ev(i,2)
438 . +ev(i,3)*ev(i,3)*ev(i,1)*ev(i,1)
439 IF(jdet(i)>zero)
THEN
440 jthird(i) = exp((-third )*log(jdet(i)))
441 j4third(i) = exp((-four_over_3)*log(jdet(i)))
452 evb(i,1)=ev(i,1)*jthird(i)
453 evb(i,2)=ev(i,2)*jthird(i)
454 evb(i,3)=ev(i,3)*jthird(i)
456 bi1(i) = evb(i,1)*evb(i,1)+evb(i,2)*evb(i,2)+evb(i,3)*evb(i,3)
458 bi2(i)= evb(i,1)*evb(i,1)*evb(i,2)*evb(i,2)
459 . + evb(i,3)*evb(i,3)*evb(i,2)*evb(i,2)
460 . + evb(i,3)*evb(i,3)*evb(i,1)*evb(i,1)
464 dphidi1(i) = c10 + two *c20 *(bi1(i)-three)+ three*c30 *(bi1(i)-three)**2
465 . + c11 *(bi2(i)-three)+ c12 *(bi2(i)-three)**2
466 . + two *c21 *(bi1(i)-three)*(bi2(i)-three)
468 dphidi2(i) = c01 + two*c02*(bi2(i)-three) +three*c03*(bi2(i)-three)**2
469 . + c11*(bi1(i)-three) + c21*(bi1(i)-three)**2
470 . + two*c12*(bi1(i)-three)*(bi2(i)-three)
471 dphidj(i) = two*d1* (jdet(i)-one) + four * d2 * (jdet(i)-one)**3 + six*d3*(jdet(i)-one)**5
473 inv2j(i)=two/
max(em20,jdet(i))
478 aa = (dphidi1(i) + dphidi2(i) * bi1(i))*inv2j(i)
479 bb = dphidi2(i) *inv2j(i)
480 cc = third* inv2j(i)* ( bi1(i)* dphidi1(i)+two* bi2(i)*dphidi2(i))
481 t1(i) = aa*evb(i,1)*evb(i,1)
485 t2(i) = aa*evb(i,2)*evb(i,2)
489 t3(i) = aa*evb(i,3)*evb(i,3)
subroutine polystress2(nel, matb, c10, c01, c20, c11, c02, c30, c21, c12, c03, d1, d2, d3, sig, bi1, bi2, jdet, flag_mul, nvarf, coefr, betaf, coefm, uvarf, rbulk, iform)
subroutine polystrest2(nel, matb, c10, c01, c20, c11, c02, c30, c21, c12, c03, d1, d2, d3, sig, bi1, bi2, jdet, flag_mul, nvarf, coefr, betaf, coefm, uvarf, cii, rbulk, iform)