Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
A_D_tensors.f90
Go to the documentation of this file.
1 !*********************************************************************
2 !* Illinois Open Source License *
3 !* *
4 !* University of Illinois/NCSA *
5 !* Open Source License *
6 !* *
7 !* Copyright@2008, University of Illinois. All rights reserved. *
8 !* *
9 !* Developed by: *
10 !* *
11 !* Center for Simulation of Advanced Rockets *
12 !* *
13 !* University of Illinois *
14 !* *
15 !* www.csar.uiuc.edu *
16 !* *
17 !* Permission is hereby granted, free of charge, to any person *
18 !* obtaining a copy of this software and associated documentation *
19 !* files (the "Software"), to deal with the Software without *
20 !* restriction, including without limitation the rights to use, *
21 !* copy, modify, merge, publish, distribute, sublicense, and/or *
22 !* sell copies of the Software, and to permit persons to whom the *
23 !* Software is furnished to do so, subject to the following *
24 !* conditions: *
25 !* *
26 !* *
27 !* @ Redistributions of source code must retain the above copyright *
28 !* notice, this list of conditions and the following disclaimers. *
29 !* *
30 !* @ Redistributions in binary form must reproduce the above *
31 !* copyright notice, this list of conditions and the following *
32 !* disclaimers in the documentation and/or other materials *
33 !* provided with the distribution. *
34 !* *
35 !* @ Neither the names of the Center for Simulation of Advanced *
36 !* Rockets, the University of Illinois, nor the names of its *
37 !* contributors may be used to endorse or promote products derived *
38 !* from this Software without specific prior written permission. *
39 !* *
40 !* THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
41 !* EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
42 !* OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
43 !* NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
44 !* COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
45 !* LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
46 !* ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
47 !* USE OR OTHER DEALINGS WITH THE SOFTWARE. *
48 !*********************************************************************
49 !* Please acknowledge The University of Illinois Center for *
50 !* Simulation of Advanced Rockets in works and publications *
51 !* resulting from this software or its derivatives. *
52 !*********************************************************************
53 SUBROUTINE a_d_tensors(Lo, Lm, L2, Mm, M2, cm, cb, cd,&
54  dbm,dbb, dbd, dmm,dmb,dmd, ddm, ddb, ddd, a2, am, l_bar)
55 
56  IMPLICIT NONE
57 
58 
59  REAL*8, DIMENSION(1:6,1:6) :: lo, lm, l2
60  REAL*8 :: cm, cb, cd
61 
62 
63  REAL*8, DIMENSION(1:6,1:6) :: mo
64  REAL*8, DIMENSION(1:6,1:6) :: mm, m2
65  REAL*8, DIMENSION(1:6,1:6) :: p
66  REAL*8, DIMENSION(1:6,1:6) :: s, sinv,si
67  REAL*8, DIMENSION(1:6,1:6) :: a,b, lst
68  REAL*8 , DIMENSION(1:6,1:6) :: l, m
69 
70  REAL*8, DIMENSION(1:6,1:6) :: dbm, dbb, dbd, dmm,dmb,dmd, ddm, ddb, ddd
71  REAL*8, DIMENSION(1:6,1:6) :: a2, am , c
72 
73  REAL*8, DIMENSION(1:6,1:6) :: l_bar, lrlbarinv
74 
75  INTEGER :: i, j
76 
77  LOGICAL :: debug
78 
79 
80  REAL*8, DIMENSION(1:6,1:6) :: dident = reshape( &
81  (/1.d0, 0.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
82  0.d0, 1.d0, 0.d0, 0.d0, 0.d0, 0.d0, &
83  0.d0, 0.d0, 1.d0, 0.d0, 0.d0, 0.d0, &
84  0.d0, 0.d0, 0.d0, 1.d0, 0.d0, 0.d0, &
85  0.d0, 0.d0, 0.d0, 0.d0, 1.d0, 0.d0, &
86  0.d0, 0.d0, 0.d0, 0.d0, 0.d0, 1.d0 /),(/6,6/) )
87 
88  debug = .false.
89 
90 !!$ DO i = 1, 6
91 !!$ PRINT*,'Lo',Lo(i,:)
92 !!$ ENDDO
93 
94  CALL invert2(lo, mo, 6)
95 
96 ! /* Type of inclusion */
97 
98 ! Returns Eshelby tensor S
99 
100  CALL eshelby(0,mo, lo, p, s)
101 ! -1
102 ! Returns S
103 
104  CALL invert2(s, sinv, 6)
105 ! I - S
106 
107  b = dident - s
108 ! Lo * ( I - S)
109  a = matmul(lo,sinv)
110 !
111 ! Hill's constrant tensor
112 !
113 ! * -1
114 ! L = S * Lo * ( I - S)
115  lst = matmul(a, b)
116 
117 !!$ PRINT*,'L*'
118 !!$
119 !!$ DO i = 1, 6
120 !!$ PRINT*,Lst(i,:)
121 !!$ ENDDO
122 
123 
124  a = lst + l_bar
125 
126 ! compute Am
127 
128  a2 = lst + lm
129  CALL invert2(a2,c,6)
130  am = matmul(c,a)
131 
132 ! compute A2
133 
134  a2 = lst + l2
135  CALL invert2(a2,c,6)
136  a2 = matmul(c,a)
137 
138 !!$ PRINT*,'am'
139 !!$ DO i = 1, 6
140 !!$ PRINT*,am(i,:)
141 !!$ ENDDO
142 !!$ PRINT*,'a2'
143 !!$ DO i = 1, 6
144 !!$ PRINT*,a2(i,:)
145 !!$ ENDDO
146 
147 
148 ! Check transformation factors
149  IF(debug)THEN
150  DO i = 1, 6
151  DO j = 1, 6
152  c(i,j) = cm*am(i,j) + (cb + cd)*a2(i,j)
153  IF (i.EQ.j .AND. (c(i,j) <= 0.9999 .OR. c(i,j) >= 1.00001))THEN
154  print*,'Incorrect Transformation tensors Am, A2'
155  stop
156  ENDIF
157  IF (i .NE. j .AND. (c(i,j) >= 1.000e-4 .OR. c(i,j) <= -1.000e-4))THEN
158  print*,'Incorrect Transformation tensors Am, A2'
159  stop
160  ENDIF
161  ENDDO
162  ENDDO
163  ENDIF
164 
165  b = lm - l_bar
166  CALL invert2(b,lrlbarinv,6)
167 
168 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
169 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
170 ! /* Dmm */
171 
172  a = dident - am
173  c = dident - cm*transpose(am)
174 
175  b = matmul(a, lrlbarinv)
176  a = matmul(b, c)
177 
178  b = matmul(a,lm)
179 
180  dmm = b
181  IF(debug)THEN
182  print*,'Dmm'
183  DO i = 1, 6
184  print*,dmm(:,i)
185  ENDDO
186  endif
187 
188 ! /* Dmb */
189 
190  a = dident - am
191  c = -1.d0*cb*transpose(a2)
192 
193  b = matmul(a, lrlbarinv)
194  a = matmul(b, c)
195 
196  b = matmul(a,l2)
197 
198  dmb = b
199 IF(debug)THEN
200  print*,'Dmb'
201  DO i = 1, 6
202  print*,dmb(:,i)
203  ENDDO
204 endif
205 
206 ! /* Dmd */
207 
208  a = dident - am
209  c = -1.d0*cd*transpose(a2)
210 
211  b = matmul(a, lrlbarinv)
212  a = matmul(b, c)
213 
214  b = matmul(a,l2)
215 
216  dmd = b
217 
218  IF(debug)THEN
219  print*,'Dmd'
220  DO i = 1, 6
221  print*,dmd(:,i)
222  ENDDO
223  ENDIF
224 
225 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
226 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
227 !!! /* Dbb */
228 
229  b = l2 - l_bar
230  CALL invert2(b,lrlbarinv,6)
231 
232  a = dident - a2
233  b = l2 - l_bar
234  c = dident - cb*transpose(a2)
235 
236  b = matmul(a, lrlbarinv)
237  a = matmul(b, c)
238 
239  b = matmul(a,l2)
240 
241  dbb = b
242  IF(debug)THEN
243  print*,'Dbb'
244  DO i = 1, 6
245  print*,dbb(:,i)
246  ENDDO
247  ENDIF
248 
249 
250 ! /* Dbm */
251 
252  a = dident - a2
253  c = -1.d0*cm*transpose(am)
254 
255  b = matmul(a, lrlbarinv)
256  a = matmul(b, c)
257 
258  b = matmul(a,lm)
259 
260  dbm = b
261  IF(debug)THEN
262  print*,'Dbm'
263  DO i = 1, 6
264  print*,dbm(:,i)
265  ENDDO
266  ENDIF
267 
268 ! /* Dbd */
269 
270 
271  a = dident - a2
272  c = -1.d0*cd*transpose(a2)
273 
274  b = matmul(a, lrlbarinv)
275  a = matmul(b, c)
276 
277  b = matmul(a,l2)
278 
279  dbd = b
280  IF(debug)THEN
281  print*,'Dbd'
282  DO i = 1, 6
283  print*,dbd(:,i)
284  ENDDO
285  ENDIF
286 
287 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
288 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
289 ! /* Ddd */
290 
291  a = dident - a2
292  c = dident - cd*transpose(a2)
293 
294  b = matmul(a, lrlbarinv)
295  a = matmul(b, c)
296 
297  b = matmul(a,l2)
298 
299  ddd = b
300 
301  IF(debug)THEN
302  print*,'Ddd'
303  DO i = 1, 6
304  print*,ddd(:,i)
305  ENDDO
306  ENDIF
307 
308 ! /* Ddm */
309 
310  a = dident - a2
311  c = -1.d0*cm*transpose(am)
312 
313  b = matmul(a, lrlbarinv)
314  a = matmul(b, c)
315 
316  b = matmul(a,lm)
317 
318  ddm = b
319  IF(debug)THEN
320  print*,'Ddm'
321  DO i = 1, 6
322  print*,ddm(:,i)
323  ENDDO
324  ENDIF
325 
326 ! /* Ddb */
327 
328  a = dident - a2
329  c = - 1.d0*cb*transpose(a2)
330 
331  b = matmul(a, lrlbarinv)
332  a = matmul(b, c)
333 
334  b = matmul(a,l2)
335 
336  ddb = b
337  IF(debug)THEN
338  print*,'Ddb'
339  DO i = 1, 6
340  print*,ddb(:,i)
341  ENDDO
342  ENDIF
343 
344 ! /* Check concentration factors */
345 
346 ! /* SUM_s=1^N Drs = I - Ar */
347 
348 
349  DO i = 1, 6
350  DO j = 1, 6
351  a(i,j) = dmm(i,j) + dmb(i,j) + dmd(i,j)
352  b(i,j) = dident(i,j) - am(i,j)
353  c(i,j) = dbm(i,j) +dbb(i,j) + dbd(i,j)
354  si(i,j) = dident(i,j) - a2(i,j)
355  s(i,j) = ddm(i,j) + ddb(i,j) + ddd(i,j)
356 
357  IF(sqrt((a(i,j) - b(i,j))*(a(i,j) - b(i,j))) >= 1.e-10 .OR. &
358  sqrt((c(i,j) - si(i,j))*(c(i,j) - si(i,j))) >= 1.e-10 .OR. &
359  sqrt((s(i,j) - si(i,j))*(s(i,j) - si(i,j))) >= 1.e-10 )THEN
360  print*,'Incorrect Concentration tensors SUM_s=1^N Drs = I - Ar'
361  stop
362  ENDIF
363  ENDDO
364  ENDDO
365 
366 
367 ! /* SUM_s=1^N Drs*Ms = 0 */
368 
369  DO i = 1, 6
370  DO j = 1, 6
371  a(i,j) = dmm(i,j)
372  b(i,j) = dmb(i,j)
373  c(i,j) = dmd(i,j)
374  ENDDO
375  ENDDO
376  s = matmul(a,mm)
377  si = matmul(b,m2)
378  a = matmul(c,m2)
379 
380  DO i = 1, 6
381  DO j = 1, 6
382  b(i,j) = s(i,j) + si(i,j) + a(i,j)
383  IF( b(i,j) >= 1.000e-10 .OR. b(i,j) <= -1.00e-10)THEN
384  print*,'A) Incorrect Concentration tensors | SUM_s=1^N Drs*Ms = 0'
385  stop
386  ENDIF
387  ENDDO
388  ENDDO
389 
390  DO i = 1, 6
391  DO j = 1, 6
392  a(i,j) = dbm(i,j)
393  b(i,j) = dbb(i,j)
394  c(i,j) = dbd(i,j)
395  ENDDO
396  ENDDO
397  s = matmul(a,mm)
398  si = matmul(b,m2)
399  a = matmul(c,m2)
400 
401  DO i = 1, 6
402  DO j = 1, 6
403  a(i,j) = s(i,j) + si(i,j) + a(i,j)
404  IF( a(i,j) >= 1.000e-10 .OR. a(i,j) <= -1.00e-10)THEN
405  print*,'B) Incorrect Concentration tensors | SUM_s=1^N Drs*Ms = 0'
406  stop
407  ENDIF
408  ENDDO
409  ENDDO
410 
411 
412  DO i = 1, 6
413  DO j = 1, 6
414  a(i,j) = ddm(i,j)
415  b(i,j) = ddb(i,j)
416  c(i,j) = ddd(i,j)
417  ENDDO
418  ENDDO
419  s = matmul(a,mm)
420  si = matmul(b,m2)
421  a = matmul(c,m2)
422 
423  DO i = 1, 6
424  DO j = 1, 6
425  a(i,j) = s(i,j) + si(i,j) + a(i,j)
426  IF( a(i,j) >= 1.000e-10 .OR. a(i,j) <= -1.00e-10)THEN
427  print*,'C) Incorrect Concentration tensors | SUM_s=1^N Drs*Ms = 0'
428  stop
429  ENDIF
430  ENDDO
431  ENDDO
432 
433 ! /* cr*Drs*Ms = cs*Mr*Dsr^T */
434 
435  a = cm*dmb
436  b = cb*dbm
437 
438  c = matmul(a,m2)
439  si = matmul(b,mm)
440 
441  DO i = 1, 6
442  DO j = 1, 6
443  IF(sqrt((c(i,j) - si(i,j))*(c(i,j) - si(i,j) )) >= 1.e-10)THEN
444  print*,'a) Incorrect Concentration tensors | cr*Drs*Ms = cs*Mr*Dsr'
445  stop
446  ENDIF
447  ENDDO
448  ENDDO
449 
450  DO i = 1, 6
451  DO j = 1,6
452  a(i,j) = cb*dbm(i,j)
453  b(i,j) = cm*dmb(i,j)
454  ENDDO
455  ENDDO
456 
457  c = matmul(a,mm)
458  si = matmul(m2,b)
459 
460  DO i = 1, 6
461  DO j = 1,6
462  IF(sqrt((c(i,j) - si(i,j))*(c(i,j) - si(i,j) )) >= 1.e-10)THEN
463  print*,'b) Incorrect Concentration tensors | cr*Drs*Ms = cs*Mr*Dsr'
464  stop
465  ENDIF
466  ENDDO
467  ENDDO
468 
469 
470 
471  DO i = 1,6
472  DO j = 1,6
473  a(i,j) = cm*dmm(i,j) + cb*dbm(i,j) + cd*ddm(i,j)
474  b(i,j) = cm*dmb(i,j) + cb*dbb(i,j) + cd*ddb(i,j)
475  c(i,j) = cm*dmd(i,j) + cb*dbd(i,j) + cd*ddd(i,j)
476  IF(a(i,j) >= 1.000e-10 .OR. a(i,j) <= -1.000e-10 .OR. &
477  b(i,j) >= 1.000e-10 .OR. b(i,j) <= -1.000e-10 .OR. &
478  c(i,j) >= 1.000e-10 .OR. c(i,j) <= -1.000e-10)THEN
479  print*,'c) Incorrect Concentration tensors | SUM_s=1^N cs*Dsr = 0'
480  stop
481  ENDIF
482  ENDDO
483  ENDDO
484 
485 
486 END SUBROUTINE a_d_tensors
487 
488 !-----------------------------------------------------------------INVERT2
489 
490 !SUBROUTINE invert2( Inv_in, a, nrow)
491 
492 ! *--------------------------------------------------------------------*
493 ! | |
494 ! | Inverts a matrix by gauss jordan elimination and computes the |
495 ! | the determinant. The matrix may be symmetric or nonsymmetric. |
496 ! | |
497 ! | <a> : a square, double precision matrix |
498 ! | <nrow> : dimensioned number of rows for 'a'. also the actual |
499 ! | sizes for inversion computations |
500 ! | <det> : determinant of the matrix ( zero if matrix is singular)|
501 ! | |
502 ! | NOTE : the matrix is overwritten by the inverse. |
503 ! | |
504 ! *--------------------------------------------------------------------*
505 !!$ IMPLICIT NONE
506 !!$
507 !!$! Argument variables
508 !!$
509 !!$ INTEGER nrow
510 !!$ REAL*8, DIMENSION(1:nrow,1:nrow) :: a, Inv_in
511 !!$ REAL*8 :: det
512 !!$
513 !!$! Local variables
514 !!$
515 !!$ INTEGER ncol, k, j, i
516 !!$
517 !!$
518 !!$ a = Inv_in
519 !!$
520 !!$! Invert matrix
521 !!$
522 !!$ det = 1.d0
523 !!$ ncol = nrow
524 !!$
525 !!$ DO k = 1, nrow
526 !!$
527 !!$ IF( a(k,k) .EQ. 0.d0 ) THEN ! Check for singular matrix
528 !!$ det = 0.d0
529 !!$ PRINT*,' Matrix is singular for inversion'
530 !!$ STOP
531 !!$ END IF
532 !!$
533 !!$ det = det * a(k, k)
534 !!$
535 !!$ DO j = 1, ncol
536 !!$ IF( j .NE. k ) a(k,j) = a(k,j) / a(k,k)
537 !!$ END DO
538 !!$
539 !!$ a(k,k) = 1.d0 / a(k,k)
540 !!$
541 !!$ DO i = 1, nrow
542 !!$ IF( i .EQ. k) CYCLE
543 !!$ DO j = 1, ncol
544 !!$ IF( j .NE. k) a(i,j) = a(i,j) - a(i,k) * a(k,j)
545 !!$ END DO
546 !!$ a(i,k) = -a(i,k) * a(k,k)
547 !!$ END DO
548 !!$
549 !!$ END DO
550 !!$
551 !!$
552 !!$ RETURN
553 !!$END SUBROUTINE invert2
554 
555 
556 SUBROUTINE vecmatvecmul(a,B,c,ndim, scaler)
557 
558  IMPLICIT NONE
559 
560  INTEGER :: ndim
561 
562  REAL*8, DIMENSION(1:ndim,1:ndim) :: b
563  REAL*8, DIMENSION(1:ndim) :: a,c
564 
565  REAL*8 :: scaler
566 
567  INTEGER i, j, k
568 
569  REAL*8 :: sum1
570  REAL*8, DIMENSION(1:ndim) :: sum2
571 
572  scaler = 0.d0
573 
574  DO i = 1, ndim
575  DO j = 1, ndim
576  sum1 = 0.d0
577  DO k = 1, ndim
578  sum1 = sum1 + b(j,k)*c(k)
579  ENDDO
580  sum2(j) = sum1
581  ENDDO
582  scaler = scaler + sum2(i)*a(i)
583  ENDDO
584 
585 END SUBROUTINE vecmatvecmul
586 
FT m(int i, int j) const
j indices k indices k
Definition: Indexing.h:6
double s
Definition: blastest.C:80
subroutine vecmatvecmul(a, B, c, ndim, scaler)
unsigned char b() const
Definition: Color.h:70
double sqrt(double d)
Definition: double.h:73
RT c() const
Definition: Line_2.h:150
subroutine a_d_tensors(Lo, Lm, L2, Mm, M2, cm, cb, cd, Dbm, Dbb, Dbd, Dmm, Dmb, Dmd, Ddm, Ddb, Ddd, A2, Am, L_bar)
Definition: A_D_tensors.f90:53
subroutine eshelby(Shape, Mo, Lo, P, S)
blockLoc i
Definition: read.cpp:79
virtual std::ostream & print(std::ostream &os) const
subroutine invert2(Inv_in, a, nrow)
j indices j
Definition: Indexing.h:6
bool debug(bool s=true)
Definition: GEM.H:193
RT a() const
Definition: Line_2.h:140