DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
constitutive_plastic_isotropic.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive_plastic_isotropic.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive_plastic_isotropic.f90"
5 !--------------------------------------------------------------------------------------------------
13 !--------------------------------------------------------------------------------------------------
14 submodule(constitutive) plastic_isotropic
15 
16  type :: tparameters
17  real(pReal) :: &
18  M, & !< Taylor factor
19  dot_gamma_0, & !< reference strain rate
20  n, & !< stress exponent
21  h0, &
22  h_ln, &
23  xi_inf, & !< maximum critical stress
24  a, &
25  c_1, &
26  c_4, &
27  c_3, &
28  c_2
29  integer :: &
30  of_debug = 0
31  logical :: &
32  dilatation
33  character(len=pStringLen), allocatable, dimension(:) :: &
34  output
35  end type tparameters
36 
37  type :: tisotropicstate
38  real(pReal), pointer, dimension(:) :: &
39  xi, &
40  gamma
41  end type tisotropicstate
42 
43 !--------------------------------------------------------------------------------------------------
44 ! containers for parameters and state
45  type(tParameters), allocatable, dimension(:) :: param
46  type(tIsotropicState), allocatable, dimension(:) :: &
47  dotState, &
48  state
49 
50 contains
51 
52 !--------------------------------------------------------------------------------------------------
55 !--------------------------------------------------------------------------------------------------
56 module subroutine plastic_isotropic_init
57 
58  integer :: &
59  Ninstance, &
60  p, &
61  NipcMyPhase, &
62  sizeState, sizeDotState
63  real(pReal) :: &
64  xi_0
65  character(len=pStringLen) :: &
66  extmsg = ''
67 
68  write(6,'(/,a)') ' <<<+- plastic_'//plasticity_isotropic_label//' init -+>>>'; flush(6)
69 
70  write(6,'(/,a)') ' Maiti and Eisenlohr, Scripta Materialia 145:37–40, 2018'
71  write(6,'(a)') ' https://doi.org/10.1016/j.scriptamat.2017.09.047'
72 
73  ninstance = count(phase_plasticity == plasticity_isotropic_id)
74  if (iand(debug_level(debug_constitutive),debug_levelbasic) /= 0) &
75  write(6,'(a16,1x,i5,/)') '# instances:',ninstance
76 
77  allocate(param(ninstance))
78  allocate(state(ninstance))
79  allocate(dotstate(ninstance))
80 
81  do p = 1, size(phase_plasticity)
82  if (phase_plasticity(p) /= plasticity_isotropic_id) cycle
83  associate(prm => param(phase_plasticityinstance(p)), &
84  dot => dotstate(phase_plasticityinstance(p)), &
85  stt => state(phase_plasticityinstance(p)), &
86  config => config_phase(p))
87 
88  prm%output = config%getStrings('(output)',defaultval=emptystringarray)
89 
90 
91 
92 
93 
94 
95  xi_0 = config%getFloat('tau0')
96  prm%xi_inf = config%getFloat('tausat')
97  prm%dot_gamma_0 = config%getFloat('gdot0')
98  prm%n = config%getFloat('n')
99  prm%h0 = config%getFloat('h0')
100  prm%M = config%getFloat('m')
101  prm%h_ln = config%getFloat('h0_slopelnrate', defaultval=0.0_preal)
102  prm%c_1 = config%getFloat('tausat_sinhfita',defaultval=0.0_preal)
103  prm%c_4 = config%getFloat('tausat_sinhfitb',defaultval=0.0_preal)
104  prm%c_3 = config%getFloat('tausat_sinhfitc',defaultval=0.0_preal)
105  prm%c_2 = config%getFloat('tausat_sinhfitd',defaultval=0.0_preal)
106  prm%a = config%getFloat('a')
107 
108  prm%dilatation = config%keyExists('/dilatation/')
109 
110 !--------------------------------------------------------------------------------------------------
111 ! sanity checks
112  if (xi_0 < 0.0_preal) extmsg = trim(extmsg)//' xi_0'
113  if (prm%dot_gamma_0 <= 0.0_preal) extmsg = trim(extmsg)//' dot_gamma_0'
114  if (prm%n <= 0.0_preal) extmsg = trim(extmsg)//' n'
115  if (prm%a <= 0.0_preal) extmsg = trim(extmsg)//' a'
116  if (prm%M <= 0.0_preal) extmsg = trim(extmsg)//' M'
117 
118 !--------------------------------------------------------------------------------------------------
119 ! allocate state arrays
120  nipcmyphase = count(material_phaseat == p) * discretization_nip
121  sizedotstate = size(['xi ','accumulated_shear'])
122  sizestate = sizedotstate
123 
124  call material_allocateplasticstate(p,nipcmyphase,sizestate,sizedotstate,0)
125 
126 !--------------------------------------------------------------------------------------------------
127 ! state aliases and initialization
128  stt%xi => plasticstate(p)%state (1,:)
129  stt%xi = xi_0
130  dot%xi => plasticstate(p)%dotState(1,:)
131  plasticstate(p)%atol(1) = config%getFloat('atol_xi',defaultval=1.0_preal)
132  if (plasticstate(p)%atol(1) < 0.0_preal) extmsg = trim(extmsg)//' atol_xi'
133 
134  stt%gamma => plasticstate(p)%state (2,:)
135  dot%gamma => plasticstate(p)%dotState(2,:)
136  plasticstate(p)%atol(2) = config%getFloat('atol_gamma',defaultval=1.0e-6_preal)
137  if (plasticstate(p)%atol(2) < 0.0_preal) extmsg = trim(extmsg)//' atol_gamma'
138  ! global alias
139  plasticstate(p)%slipRate => plasticstate(p)%dotState(2:2,:)
140 
141  plasticstate(p)%state0 = plasticstate(p)%state ! ToDo: this could be done centrally
142 
143  end associate
144 
145 !--------------------------------------------------------------------------------------------------
146 ! exit if any parameter is out of range
147  if (extmsg /= '') call io_error(211,ext_msg=trim(extmsg)//'('//plasticity_isotropic_label//')')
148 
149  enddo
150 
151 end subroutine plastic_isotropic_init
152 
153 
154 !--------------------------------------------------------------------------------------------------
156 !--------------------------------------------------------------------------------------------------
157 module subroutine plastic_isotropic_lpanditstangent(lp,dlp_dmp,mp,instance,of)
158 
159  real(pReal), dimension(3,3), intent(out) :: &
160  Lp
161  real(pReal), dimension(3,3,3,3), intent(out) :: &
162  dLp_dMp
163 
164  real(pReal), dimension(3,3), intent(in) :: &
165  Mp
166  integer, intent(in) :: &
167  instance, &
168  of
169 
170  real(pReal), dimension(3,3) :: &
171  Mp_dev
172  real(pReal) :: &
173  dot_gamma, & !< strainrate
174  norm_Mp_dev, & !< norm of the deviatoric part of the Mandel stress
175  squarenorm_Mp_dev
176  integer :: &
177  k, l, m, n
178 
179  associate(prm => param(instance), stt => state(instance))
180 
181  mp_dev = math_deviatoric33(mp)
182  squarenorm_mp_dev = math_tensordot(mp_dev,mp_dev)
183  norm_mp_dev = sqrt(squarenorm_mp_dev)
184 
185  if (norm_mp_dev > 0.0_preal) then
186  dot_gamma = prm%dot_gamma_0 * (sqrt(1.5_preal) * norm_mp_dev/(prm%M*stt%xi(of))) **prm%n
187 
188  lp = dot_gamma/prm%M * mp_dev/norm_mp_dev
189 # 194 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive_plastic_isotropic.f90"
190  forall (k=1:3,l=1:3,m=1:3,n=1:3) &
191  dlp_dmp(k,l,m,n) = (prm%n-1.0_preal) * mp_dev(k,l)*mp_dev(m,n) / squarenorm_mp_dev
192  forall (k=1:3,l=1:3) &
193  dlp_dmp(k,l,k,l) = dlp_dmp(k,l,k,l) + 1.0_preal
194  forall (k=1:3,m=1:3) &
195  dlp_dmp(k,k,m,m) = dlp_dmp(k,k,m,m) - 1.0_preal/3.0_preal
196  dlp_dmp = dot_gamma / prm%M * dlp_dmp / norm_mp_dev
197  else
198  lp = 0.0_preal
199  dlp_dmp = 0.0_preal
200  end if
201 
202  end associate
203 
204 end subroutine plastic_isotropic_lpanditstangent
205 
206 
207 !--------------------------------------------------------------------------------------------------
209 !--------------------------------------------------------------------------------------------------
210 module subroutine plastic_isotropic_lianditstangent(li,dli_dmi,mi,instance,of)
211 
212  real(pReal), dimension(3,3), intent(out) :: &
213  Li
214  real(pReal), dimension(3,3,3,3), intent(out) :: &
215  dLi_dMi
216 
217  real(pReal), dimension(3,3), intent(in) :: &
218  Mi
219  integer, intent(in) :: &
220  instance, &
221  of
222 
223  real(pReal) :: &
224  tr
225  integer :: &
226  k, l, m, n
227 
228  associate(prm => param(instance), stt => state(instance))
229 
230  tr=math_trace33(math_spherical33(mi))
231 
232  if (prm%dilatation .and. abs(tr) > 0.0_preal) then ! no stress or J2 plasticity --> Li and its derivative are zero
233  li = math_i3 &
234  * prm%dot_gamma_0/prm%M * (3.0_preal*prm%M*stt%xi(of))**(-prm%n) &
235  * tr * abs(tr)**(prm%n-1.0_preal)
236 
237 # 249 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive_plastic_isotropic.f90"
238 
239  forall (k=1:3,l=1:3,m=1:3,n=1:3) &
240  dli_dmi(k,l,m,n) = prm%n / tr * li(k,l) * math_i3(m,n)
241 
242  else
243  li = 0.0_preal
244  dli_dmi = 0.0_preal
245  endif
246 
247  end associate
248 
249  end subroutine plastic_isotropic_lianditstangent
250 
251 
252 !--------------------------------------------------------------------------------------------------
254 !--------------------------------------------------------------------------------------------------
255 module subroutine plastic_isotropic_dotstate(mp,instance,of)
256 
257  real(pReal), dimension(3,3), intent(in) :: &
258  Mp
259  integer, intent(in) :: &
260  instance, &
261  of
262 
263  real(pReal) :: &
264  dot_gamma, & !< strainrate
265  xi_inf_star, & !< saturation xi
266  norm_Mp
267 
268  associate(prm => param(instance), stt => state(instance), dot => dotstate(instance))
269 
270  if (prm%dilatation) then
271  norm_mp = sqrt(math_tensordot(mp,mp))
272  else
273  norm_mp = sqrt(math_tensordot(math_deviatoric33(mp),math_deviatoric33(mp)))
274  endif
275 
276  dot_gamma = prm%dot_gamma_0 * (sqrt(1.5_preal) * norm_mp /(prm%M*stt%xi(of))) **prm%n
277 
278  if (dot_gamma > 1e-12_preal) then
279  if (deq0(prm%c_1)) then
280  xi_inf_star = prm%xi_inf
281  else
282  xi_inf_star = prm%xi_inf &
283  + asinh( (dot_gamma / prm%c_1)**(1.0_preal / prm%c_2))**(1.0_preal / prm%c_3) &
284  / prm%c_4 * (dot_gamma / prm%dot_gamma_0)**(1.0_preal / prm%n)
285  endif
286  dot%xi(of) = dot_gamma &
287  * ( prm%h0 + prm%h_ln * log(dot_gamma) ) &
288  * abs( 1.0_preal - stt%xi(of)/xi_inf_star )**prm%a &
289  * sign(1.0_preal, 1.0_preal - stt%xi(of)/xi_inf_star)
290  else
291  dot%xi(of) = 0.0_preal
292  endif
293 
294  dot%gamma(of) = dot_gamma ! ToDo: not really used
295 
296  end associate
297 
298 end subroutine plastic_isotropic_dotstate
299 
300 
301 !--------------------------------------------------------------------------------------------------
303 !--------------------------------------------------------------------------------------------------
304 module subroutine plastic_isotropic_results(instance,group)
305 
306  integer, intent(in) :: instance
307  character(len=*), intent(in) :: group
308 
309  integer :: o
310 
311  associate(prm => param(instance), stt => state(instance))
312  outputsloop: do o = 1,size(prm%output)
313  select case(trim(prm%output(o)))
314  case ('flowstress') ! ToDo: should be 'xi'
315  call results_writedataset(group,stt%xi,'xi','resistance against plastic flow','Pa')
316  end select
317  enddo outputsloop
318  end associate
319 
320 end subroutine plastic_isotropic_results
321 
322 
323 end submodule plastic_isotropic
config
Reads in the material configuration from file.
Definition: config.f90:13
constitutive
elasticity, plasticity, internal microstructure state
Definition: constitutive.f90:10