Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
HUANG_Const_Model.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 huang_const_model(dfgrad,matrix,nmatrix, &
54  particle,nparticle,nparticletype,interfac,ninterfac,stress, strain, ilarge, ismall)
55 
56 !!****f* Rocfrac/Source/huang_const_model.f90
57 !!
58 !! NAME
59 !! huang_const_model
60 !!
61 !! FUNCTION
62 !!
63 !! this program is for the constitutive modeling of solid propellants
64 !! accounting for the effect of particle/matrix interface debonding. the
65 !! program can handle one or two types of particles that have the same
66 !! elastic moduli but different radii.
67 !!
68 !! INPUTS
69 !!
70 !!----- all variables above except the last few, i.e.,
71 !! dfgrad,matrix,nmatrix,particle,nparticle,
72 !! interfac,ninterfac
73 !! dfgrad: deformation gradient
74 !! nmatrix: number of matrix properties
75 !! matrix: properties of the matrix
76 !! matrix(1): young's modulus of the matrix
77 !! matrix(2): poisson's ratio of the matrix
78 !! matrix(3): volume fraction of the matrix
79 !! nparticletype: number of the particle types
80 !! nparticletype is no more than 2 in this program!
81 !! nparticle: number particle properties for each type
82 !! particle: properties of particles
83 !! particle(1,i): young's modulus of type-i particles
84 !! particle(2,i): poisson's ratio of type-i particles
85 !! particle(3,i): volume fraction of type-i particles
86 !! particle(4,i): radius of type-i particles
87 !! ninterfac: number of interface properties
88 !! interfac: properties of the interface
89 !! interfac(1): strength of the interface
90 !! interfac(2): linear modulus of the interface
91 !! interfac(3): softening modulus of the interface
92 !! stress: stress tensor
93 !! strain: strain tensor
94 !! ilarge, ismall: damage information for large and small particles
95 !! ilarge=1: large particles not failed
96 !! ilarge=2: large particles is failing
97 !! ilarge=3: large particles completely failed
98 !! ismall=1: small particles not failed
99 !! ismall=2: small particles is failing
100 !! ismall=3: small particles completely failed
101 !!
102 !! OUTPUT
103 !!
104 !! stress -- Stress
105 !! Strain -- Strain
106 !! ilarge, ismall -- failing state of large and small particles.
107 !!****
108 
109 !----- arrays for input/output
110  REAL*8 dfgrad(3,3),matrix(nmatrix), &
111  particle(nparticle,nparticletype),interfac(ninterfac), &
112  stress(3,3)
113 
114  REAL*8 :: ilarge, ismall
115 
116 !----- arrays for the internal use in the subroutine
117  REAL*8 alpha(nparticletype),alphaprime(nparticletype), &
118  bulkp(nparticletype),shearp(nparticletype), &
119  strain(3,3),stressprime(3,3),strainprime(3,3), &
120  mstrainpt(5),mstresspt(5)
121 
122 !----- variables for internal use in the subroutine
123  REAL*8 em,posm,bulkm,shearm,bulkcomposite,shearcomposite,strength, &
124  kinthard,kintsoft,stressmean,strainmean
125 
126 !----- the green strain
127  DO i=1,3
128  DO j=1,3
129  strain(i,j)= dfgrad(1,i)*dfgrad(1,j) &
130  +dfgrad(2,i)*dfgrad(2,j) &
131  +dfgrad(3,i)*dfgrad(3,j)
132  IF (i.EQ.j) THEN
133  strain(i,j)=(strain(i,j)-1)*0.5d0
134  ELSE
135  strain(i,j)=strain(i,j)*0.5d0
136  END IF
137  ENDDO
138  ENDDO
139 
140 !----- the mean and deviatoric strains
141  strainmean=(strain(1,1)+strain(2,2)+strain(3,3))/3.d0
142  DO i=1,3
143  DO j=1,3
144  IF (i.EQ.j) THEN
145  strainprime(i,j)=strain(i,j)-strainmean
146  ELSE
147  strainprime(i,j)=strain(i,j)
148  END IF
149  ENDDO
150  ENDDO
151 
152 !----- parameters for particles: alpha and alphaprime
153  em = matrix(1)
154  posm = matrix(2)
155  bulkm= em/(3.d0*(1.d0-2.d0*posm))
156  shearm=em/(2.d0*(1.d0+posm))
157  strength=interfac(1)
158  kinthard=interfac(2)
159  kintsoft=interfac(3)
160 
161  DO i=1,nparticletype
162  bulkp(i)=particle(1,i)/(3*(1-2*particle(2,i)))
163  shearp(i)=particle(1,i)/(2*(1+particle(2,i)))
164  alpha(i)=3.d0*(1-posm)/(2*em) &
165  /( 1.d0/(kinthard*particle(4,i)) &
166  +1.d0/(3.d0*bulkp(i)) &
167  +1.d0/(4.d0*shearm))
168  alphaprime(i)=-3.d0*(1.d0-posm)/(2.d0*em) &
169  /(-1.d0/(kintsoft*particle(4,i)) &
170  +1.d0/(3.d0*bulkp(i)) &
171  +1.d0/(4.d0*shearm))
172 
173  ENDDO
174 
175 
176  c1=particle(3,1)
177  c2=particle(3,2)
178  a1=particle(4,1)
179  a2=particle(4,2)
180  c=c1+c2
181 
182  alpha1=alpha(1)
183  alpha2=alpha(2)
184  alphaprime1=alphaprime(1)
185  alphaprime2=alphaprime(2)
186 
187 !----- critical particle radius
188  aprime=1.d0/(1.d0/(4.d0*shearm)+1.d0/(3.d0*bulkp(1)))/kintsoft
189 
190 !----- the mean stress and strain of the composite at the transition point
191 ! between different stages.
192 ! path2:(i,i)->(ii,i)->(iii,i)->(iii,ii)->(iii,iii)
193  mstrainpt(1)=0.d0
194  mstresspt(1)=0.d0
195 ! (i,i)->(ii,i)
196  mstrainpt(2)=strength/(2.d0*em*alpha1) &
197  *(2.d0*(1.d0-2.d0*posm)-(1.d0+posm)*(-c+c2*alpha2+c1*alpha1))
198  mstresspt(2)=strength*(1.d0-c+c2*alpha2+c1*alpha1)/alpha1
199 ! (ii,i)->(iii,i)
200  mstrainpt(3)=strength*(1.d0/alpha1+1.d0/alphaprime1) &
201  *(2.d0*(1.d0-2.d0*posm)+(1.d0+posm)*(c-c2*alpha2))/(2.d0*em)
202  mstresspt(3)=strength*(1.d0/alpha1+1.d0/alphaprime1)*(1.d0-c+c2*alpha2)
203 ! (iii,i)->(iii,ii)
204  mstrainpt(4)=strength*(2.d0*(1.d0-2.d0*posm)+c*(1.d0+posm)-(1.d0+posm)*c2*alpha2) &
205  /(2.d0*em*alpha2)
206  mstresspt(4)=strength*(1.d0-c+c2*alpha2)/alpha2
207 ! (iii,ii)->(iii,iii)
208  mstrainpt(5)=strength/(2.d0*em) &
209  *(1/alpha2+1/alphaprime2)*(2*(1-2*posm)+c*(1+posm))
210  mstresspt(5)=(1.d0-c)*strength*(1.d0/alpha2+1.d0/alphaprime2)
211 
212 ! path1:(i,i)->(ii,i)->(ii,ii)->(iii,ii)->(iii,iii)
213  IF (a1.LT.aprime) THEN
214 ! (ii,i)->(ii,ii)
215  mstrainpt(3)=strength/(2.d0*em) &
216  *(2.d0*(1.d0-2.d0*posm)/alpha2 &
217  -(1.d0+posm)*(c+c1*alphaprime1*(1.d0/alpha1-1.d0/alpha2) &
218  -c/alpha2))
219  mstresspt(3)=strength &
220  *((1.d0-c)/alpha2+c+c1*alphaprime1 &
221  *(1.d0/alpha1-1.d0/alpha2))
222 ! (ii,ii)->(iii,ii)
223  mstrainpt(4)=strength/(2.d0*em) &
224  *((2.d0*(1.d0-2.d0*posm)+c*(1.d0+posm)) &
225  *(1.d0/alpha1+1.d0/alphaprime1) &
226  -(1.d0+posm)*c2*(1.d0-alphaprime2/alpha1 &
227  -alphaprime2/alphaprime1 &
228  +alphaprime2/alpha2))
229  mstresspt(4)=strength*((1.d0-c)*(1.d0/alpha1+1.d0/alphaprime1) &
230  +c2*(1.d0-alphaprime2/alpha1 &
231  -alphaprime2/alphaprime1 &
232  +alphaprime2/alpha2))
233  END IF
234 
235 !---- mean stress in the composite
236  DO i=1,4
237  IF (strainmean.GE.mstrainpt(i).AND. &
238  strainmean.LT.mstrainpt(i+1)) THEN
239  stressmean=mstresspt(i)+(strainmean-mstrainpt(i)) &
240  *(mstresspt(i+1)-mstresspt(i)) &
241  /(mstrainpt(i+1)-mstrainpt(i))
242 
243  IF(i.EQ.1) THEN
244  ilarge=1
245  ismall=1
246  ELSE IF(i.EQ.2) THEN
247  ilarge=2
248  ismall=1
249  ELSE IF(i.EQ.3) THEN
250  IF(a1.LT.aprime) THEN
251  ilarge=2
252  ismall=2
253  ELSE
254  ilarge=3
255  ismall=1
256  ENDIF
257  ELSE IF(i.EQ.4) THEN
258  ilarge=3
259  ismall=2
260  ENDIF
261  END IF
262  ENDDO
263  IF (strainmean.GE.mstrainpt(5)) THEN
264  stressmean=mstresspt(5)*strainmean/mstrainpt(5)
265  ilarge=3
266  ismall=3
267  END IF
268  IF (strainmean.LT.0) THEN
269  bulkcomposite=bulkm+c*(bulkp(1)-bulkm)*3.d0*(1-posm) &
270  /(3.d0*(1.d0-posm)+(1.d0+posm) &
271  *(bulkp(1)/bulkm-1.d0)*(1.d0-c))
272  stressmean=3.d0*bulkcomposite*strainmean
273  ilarge=1
274  ismall=1
275  END IF
276 
277 !----- deviatoric stress
278  shearcomposite=shearm+c*(shearp(1)-shearm)*15.d0*(1.d0-posm) &
279  /(15.d0*(1.d0-posm)+2.d0*(4.d0-5.d0*posm) &
280  *(shearp(1)/shearm-1.d0)*(1.d0-c))
281  DO i=1,3
282  DO j=1,3
283  stressprime(i,j)=2.d0*shearcomposite*strainprime(i,j)
284  ENDDO
285  ENDDO
286 
287 !----- update the stress
288  DO i=1,3
289  DO j=1,3
290  IF (i.EQ.j) THEN
291  stress(i,j)=stressprime(i,j)+stressmean
292  ELSE
293  stress(i,j)=stressprime(i,j)
294  END IF
295  ENDDO
296  ENDDO
297 
298 END SUBROUTINE huang_const_model
299 
subroutine huang_const_model(dfgrad, matrix, nmatrix, particle, nparticle, nparticletype, interfac, ninterfac, stress, strain, ilarge, ismall)
RT c() const
Definition: Line_2.h:150
blockLoc i
Definition: read.cpp:79
CImg< T > & matrix()
Realign pixel values of the instance image as a square matrix.
Definition: CImg.h:13343
j indices j
Definition: Indexing.h:6
unsigned char alpha() const
Definition: Color.h:75