DAMASK with grid solvers  Revision: v2.0.3-2204-gdb1f2151
The Düsseldorf Advanced Material Simulation Kit with Grid Solvers
constitutive.f90
Go to the documentation of this file.
1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive.f90"
2 # 1 "<built-in>"
3 # 1 "<command-line>"
4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/constitutive.f90"
5 !--------------------------------------------------------------------------------------------------
9 !--------------------------------------------------------------------------------------------------
11  use prec
12  use math
13  use rotations
14  use debug
15  use numerics
16  use io
17  use config
18  use material
19  use results
20  use lattice
21  use discretization
32 
33  implicit none
34  private
35 
36  integer, public, protected :: &
39 
40  interface
41 
42  module subroutine plastic_none_init
43  end subroutine plastic_none_init
44 
45  module subroutine plastic_isotropic_init
46  end subroutine plastic_isotropic_init
47 
48  module subroutine plastic_phenopowerlaw_init
49  end subroutine plastic_phenopowerlaw_init
50 
51  module subroutine plastic_kinehardening_init
52  end subroutine plastic_kinehardening_init
53 
54  module subroutine plastic_dislotwin_init
55  end subroutine plastic_dislotwin_init
56 
57  module subroutine plastic_disloucla_init
58  end subroutine plastic_disloucla_init
59 
60  module subroutine plastic_nonlocal_init
61  end subroutine plastic_nonlocal_init
62 
63 
64  module subroutine plastic_isotropic_lpanditstangent(lp,dlp_dmp,mp,instance,of)
65  real(preal), dimension(3,3), intent(out) :: &
66  lp
67  real(preal), dimension(3,3,3,3), intent(out) :: &
68  dlp_dmp
69 
70  real(preal), dimension(3,3), intent(in) :: &
71  mp
72  integer, intent(in) :: &
73  instance, &
74  of
75  end subroutine plastic_isotropic_lpanditstangent
76 
77  pure module subroutine plastic_phenopowerlaw_lpanditstangent(lp,dlp_dmp,mp,instance,of)
78  real(preal), dimension(3,3), intent(out) :: &
79  lp
80  real(preal), dimension(3,3,3,3), intent(out) :: &
81  dlp_dmp
82 
83  real(preal), dimension(3,3), intent(in) :: &
84  mp
85  integer, intent(in) :: &
86  instance, &
87  of
88  end subroutine plastic_phenopowerlaw_lpanditstangent
89 
90  pure module subroutine plastic_kinehardening_lpanditstangent(lp,dlp_dmp,mp,instance,of)
91  real(preal), dimension(3,3), intent(out) :: &
92  lp
93  real(preal), dimension(3,3,3,3), intent(out) :: &
94  dlp_dmp
95 
96  real(preal), dimension(3,3), intent(in) :: &
97  mp
98  integer, intent(in) :: &
99  instance, &
100  of
101  end subroutine plastic_kinehardening_lpanditstangent
102 
103  module subroutine plastic_dislotwin_lpanditstangent(lp,dlp_dmp,mp,t,instance,of)
104  real(preal), dimension(3,3), intent(out) :: &
105  lp
106  real(preal), dimension(3,3,3,3), intent(out) :: &
107  dlp_dmp
108 
109  real(preal), dimension(3,3), intent(in) :: &
110  mp
111  real(preal), intent(in) :: &
112  t
113  integer, intent(in) :: &
114  instance, &
115  of
116  end subroutine plastic_dislotwin_lpanditstangent
117 
118  pure module subroutine plastic_disloucla_lpanditstangent(lp,dlp_dmp,mp,t,instance,of)
119  real(preal), dimension(3,3), intent(out) :: &
120  lp
121  real(preal), dimension(3,3,3,3), intent(out) :: &
122  dlp_dmp
123 
124  real(preal), dimension(3,3), intent(in) :: &
125  mp
126  real(preal), intent(in) :: &
127  t
128  integer, intent(in) :: &
129  instance, &
130  of
131  end subroutine plastic_disloucla_lpanditstangent
132 
133  module subroutine plastic_nonlocal_lpanditstangent(lp,dlp_dmp, &
134  mp,temperature,instance,of,ip,el)
135  real(preal), dimension(3,3), intent(out) :: &
136  lp
137  real(preal), dimension(3,3,3,3), intent(out) :: &
138  dlp_dmp
139 
140  real(preal), dimension(3,3), intent(in) :: &
141  mp
142  real(preal), intent(in) :: &
144  integer, intent(in) :: &
145  instance, &
146  of, &
147  ip, & !< current integration point
148  el
149  end subroutine plastic_nonlocal_lpanditstangent
150 
151 
152  module subroutine plastic_isotropic_lianditstangent(li,dli_dmi,mi,instance,of)
153  real(preal), dimension(3,3), intent(out) :: &
154  li
155  real(preal), dimension(3,3,3,3), intent(out) :: &
156  dli_dmi
157 
158  real(preal), dimension(3,3), intent(in) :: &
159  mi
160  integer, intent(in) :: &
161  instance, &
162  of
163  end subroutine plastic_isotropic_lianditstangent
164 
165 
166  module subroutine plastic_isotropic_dotstate(mp,instance,of)
167  real(preal), dimension(3,3), intent(in) :: &
168  mp
169  integer, intent(in) :: &
170  instance, &
171  of
172  end subroutine plastic_isotropic_dotstate
173 
174  module subroutine plastic_phenopowerlaw_dotstate(mp,instance,of)
175  real(preal), dimension(3,3), intent(in) :: &
176  mp
177  integer, intent(in) :: &
178  instance, &
179  of
180  end subroutine plastic_phenopowerlaw_dotstate
181 
182  module subroutine plastic_kinehardening_dotstate(mp,instance,of)
183  real(preal), dimension(3,3), intent(in) :: &
184  mp
185  integer, intent(in) :: &
186  instance, &
187  of
188  end subroutine plastic_kinehardening_dotstate
189 
190  module subroutine plastic_dislotwin_dotstate(mp,t,instance,of)
191  real(preal), dimension(3,3), intent(in) :: &
192  mp
193  real(preal), intent(in) :: &
194  t
195  integer, intent(in) :: &
196  instance, &
197  of
198  end subroutine plastic_dislotwin_dotstate
199 
200  module subroutine plastic_disloucla_dotstate(mp,t,instance,of)
201  real(preal), dimension(3,3), intent(in) :: &
202  mp
203  real(preal), intent(in) :: &
204  t
205  integer, intent(in) :: &
206  instance, &
207  of
208  end subroutine plastic_disloucla_dotstate
209 
210  module subroutine plastic_nonlocal_dotstate(mp, f, fp, temperature,timestep, &
211  instance,of,ip,el)
212  real(preal), dimension(3,3), intent(in) ::&
213  mp
214  real(preal), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem), intent(in) :: &
215  f, & !< deformation gradient
216  fp
217  real(preal), intent(in) :: &
218  temperature, & !< temperature
219  timestep
220  integer, intent(in) :: &
221  instance, &
222  of, &
223  ip, & !< current integration point
224  el
225  end subroutine plastic_nonlocal_dotstate
226 
227 
228  module subroutine plastic_dislotwin_dependentstate(t,instance,of)
229  integer, intent(in) :: &
230  instance, &
231  of
232  real(preal), intent(in) :: &
233  t
234  end subroutine plastic_dislotwin_dependentstate
235 
236  module subroutine plastic_disloucla_dependentstate(instance,of)
237  integer, intent(in) :: &
238  instance, &
239  of
240  end subroutine plastic_disloucla_dependentstate
241 
242  module subroutine plastic_nonlocal_dependentstate(f, fp, instance, of, ip, el)
243  real(preal), dimension(3,3), intent(in) :: &
244  f, &
245  fp
246  integer, intent(in) :: &
247  instance, &
248  of, &
249  ip, &
250  el
251  end subroutine plastic_nonlocal_dependentstate
252 
253 
254  module subroutine plastic_kinehardening_deltastate(mp,instance,of)
255  real(preal), dimension(3,3), intent(in) :: &
256  mp
257  integer, intent(in) :: &
258  instance, &
259  of
260  end subroutine plastic_kinehardening_deltastate
261 
262  module subroutine plastic_nonlocal_deltastate(mp,instance,of,ip,el)
263  real(preal), dimension(3,3), intent(in) :: &
264  mp
265  integer, intent(in) :: &
266  instance, &
267  of, &
268  ip, &
269  el
270  end subroutine plastic_nonlocal_deltastate
271 
272 
273  module function plastic_dislotwin_homogenizedc(ipc,ip,el) result(homogenizedc)
274  real(preal), dimension(6,6) :: &
275  homogenizedc
276  integer, intent(in) :: &
277  ipc, & !< component-ID of integration point
278  ip, & !< integration point
279  el
280  end function plastic_dislotwin_homogenizedc
281 
282  module subroutine plastic_nonlocal_updatecompatibility(orientation,instance,i,e)
283  integer, intent(in) :: &
284  instance, &
285  i, &
286  e
287  type(rotation), dimension(1,discretization_nIP,discretization_nElem), intent(in) :: &
288  orientation
289  end subroutine plastic_nonlocal_updatecompatibility
290 
291 
292  module subroutine plastic_isotropic_results(instance,group)
293  integer, intent(in) :: instance
294  character(len=*), intent(in) :: group
295  end subroutine plastic_isotropic_results
296 
297  module subroutine plastic_phenopowerlaw_results(instance,group)
298  integer, intent(in) :: instance
299  character(len=*), intent(in) :: group
300  end subroutine plastic_phenopowerlaw_results
301 
302  module subroutine plastic_kinehardening_results(instance,group)
303  integer, intent(in) :: instance
304  character(len=*), intent(in) :: group
305  end subroutine plastic_kinehardening_results
306 
307  module subroutine plastic_dislotwin_results(instance,group)
308  integer, intent(in) :: instance
309  character(len=*), intent(in) :: group
310  end subroutine plastic_dislotwin_results
311 
312  module subroutine plastic_disloucla_results(instance,group)
313  integer, intent(in) :: instance
314  character(len=*), intent(in) :: group
315  end subroutine plastic_disloucla_results
316 
317  module subroutine plastic_nonlocal_results(instance,group)
318  integer, intent(in) :: instance
319  character(len=*), intent(in) :: group
320  end subroutine plastic_nonlocal_results
321 
322  end interface
323 
324  public :: &
325  plastic_nonlocal_updatecompatibility, &
326  constitutive_init, &
327  constitutive_homogenizedc, &
328  constitutive_dependentstate, &
329  constitutive_lpanditstangents, &
330  constitutive_lianditstangents, &
331  constitutive_initialfi, &
332  constitutive_sanditstangents, &
333  constitutive_collectdotstate, &
334  constitutive_collectdeltastate, &
335  constitutive_results
336 
337 contains
338 
339 
340 !--------------------------------------------------------------------------------------------------
342 !--------------------------------------------------------------------------------------------------
343 subroutine constitutive_init
344 
345  integer :: &
346  ph, & !< counter in phase loop
347  s
348 
349 !--------------------------------------------------------------------------------------------------
350 ! initialized plasticity
351  if (any(phase_plasticity == plasticity_none_id)) call plastic_none_init
352  if (any(phase_plasticity == plasticity_isotropic_id)) call plastic_isotropic_init
353  if (any(phase_plasticity == plasticity_phenopowerlaw_id)) call plastic_phenopowerlaw_init
354  if (any(phase_plasticity == plasticity_kinehardening_id)) call plastic_kinehardening_init
355  if (any(phase_plasticity == plasticity_dislotwin_id)) call plastic_dislotwin_init
356  if (any(phase_plasticity == plasticity_disloucla_id)) call plastic_disloucla_init
357  if (any(phase_plasticity == plasticity_nonlocal_id)) then
358  call plastic_nonlocal_init
359  else
361  endif
362 !--------------------------------------------------------------------------------------------------
363 ! initialize source mechanisms
370 
371 !--------------------------------------------------------------------------------------------------
372 ! initialize kinematic mechanisms
376 
377  write(6,'(/,a)') ' <<<+- constitutive init -+>>>'; flush(6)
378 
379  constitutive_source_maxsizedotstate = 0
380  phaseloop2:do ph = 1,material_nphase
381 !--------------------------------------------------------------------------------------------------
382 ! partition and inititalize state
383  plasticstate(ph)%partionedState0 = plasticstate(ph)%state0
384  plasticstate(ph)%state = plasticstate(ph)%partionedState0
385  forall(s = 1:phase_nsources(ph))
386  sourcestate(ph)%p(s)%partionedState0 = sourcestate(ph)%p(s)%state0
387  sourcestate(ph)%p(s)%state = sourcestate(ph)%p(s)%partionedState0
388  end forall
389 !--------------------------------------------------------------------------------------------------
390 ! determine max size of source state
391  constitutive_source_maxsizedotstate = max(constitutive_source_maxsizedotstate, &
392  maxval(sourcestate(ph)%p%sizeDotState))
393  enddo phaseloop2
394  constitutive_plasticity_maxsizedotstate = maxval(plasticstate%sizeDotState)
395 
396 end subroutine constitutive_init
397 
398 
399 !--------------------------------------------------------------------------------------------------
402 !--------------------------------------------------------------------------------------------------
403 function constitutive_homogenizedc(ipc,ip,el)
404 
405  real(preal), dimension(6,6) :: constitutive_homogenizedc
406  integer, intent(in) :: &
407  ipc, & !< component-ID of integration point
408  ip, & !< integration point
409  el
410 
411  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
412  case (plasticity_dislotwin_id) plasticitytype
413  constitutive_homogenizedc = plastic_dislotwin_homogenizedc(ipc,ip,el)
414  case default plasticitytype
415  constitutive_homogenizedc = lattice_c66(1:6,1:6,material_phaseat(ipc,el))
416  end select plasticitytype
417 
418 end function constitutive_homogenizedc
419 
420 
421 !--------------------------------------------------------------------------------------------------
423 !--------------------------------------------------------------------------------------------------
424 subroutine constitutive_dependentstate(F, Fp, ipc, ip, el)
425 
426  integer, intent(in) :: &
427  ipc, & !< component-ID of integration point
428  ip, & !< integration point
429  el
430  real(preal), intent(in), dimension(3,3) :: &
431  f, & !< elastic deformation gradient
432  fp
433  integer :: &
434  ho, & !< homogenization
435  tme, & !< thermal member position
436  instance, of
437 
439  tme = thermalmapping(ho)%p(ip,el)
440  of = material_phasememberat(ipc,ip,el)
441  instance = phase_plasticityinstance(material_phaseat(ipc,el))
442 
443  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
444  case (plasticity_dislotwin_id) plasticitytype
445  call plastic_dislotwin_dependentstate(temperature(ho)%p(tme),instance,of)
446  case (plasticity_disloucla_id) plasticitytype
447  call plastic_disloucla_dependentstate(instance,of)
448  case (plasticity_nonlocal_id) plasticitytype
449  call plastic_nonlocal_dependentstate (f,fp,instance,of,ip,el)
450  end select plasticitytype
451 
452 end subroutine constitutive_dependentstate
453 
454 
455 !--------------------------------------------------------------------------------------------------
457 ! ToDo: Discuss wheter it makes sense if crystallite handles the configuration conversion, i.e.
458 ! Mp in, dLp_dMp out
459 !--------------------------------------------------------------------------------------------------
460 subroutine constitutive_lpanditstangents(Lp, dLp_dS, dLp_dFi, &
461  S, Fi, ipc, ip, el)
462  integer, intent(in) :: &
463  ipc, & !< component-ID of integration point
464  ip, & !< integration point
465  el
466  real(preal), intent(in), dimension(3,3) :: &
467  s, & !< 2nd Piola-Kirchhoff stress
468  fi
469  real(preal), intent(out), dimension(3,3) :: &
470  lp
471  real(preal), intent(out), dimension(3,3,3,3) :: &
472  dlp_ds, &
473  dlp_dfi
474  real(preal), dimension(3,3,3,3) :: &
475  dlp_dmp
476  real(preal), dimension(3,3) :: &
477  mp
478  integer :: &
479  ho, & !< homogenization
480  tme
481  integer :: &
482  i, j, instance, of
483 
485  tme = thermalmapping(ho)%p(ip,el)
486 
487  mp = matmul(matmul(transpose(fi),fi),s)
488  of = material_phasememberat(ipc,ip,el)
489  instance = phase_plasticityinstance(material_phaseat(ipc,el))
490 
491  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
492 
493  case (plasticity_none_id) plasticitytype
494  lp = 0.0_preal
495  dlp_dmp = 0.0_preal
496 
497  case (plasticity_isotropic_id) plasticitytype
498  call plastic_isotropic_lpanditstangent (lp,dlp_dmp,mp,instance,of)
499 
500  case (plasticity_phenopowerlaw_id) plasticitytype
501  call plastic_phenopowerlaw_lpanditstangent(lp,dlp_dmp,mp,instance,of)
502 
503  case (plasticity_kinehardening_id) plasticitytype
504  call plastic_kinehardening_lpanditstangent(lp,dlp_dmp,mp,instance,of)
505 
506  case (plasticity_nonlocal_id) plasticitytype
507  call plastic_nonlocal_lpanditstangent (lp,dlp_dmp,mp, temperature(ho)%p(tme),instance,of,ip,el)
508 
509  case (plasticity_dislotwin_id) plasticitytype
510  call plastic_dislotwin_lpanditstangent (lp,dlp_dmp,mp,temperature(ho)%p(tme),instance,of)
511 
512  case (plasticity_disloucla_id) plasticitytype
513  call plastic_disloucla_lpanditstangent (lp,dlp_dmp,mp,temperature(ho)%p(tme),instance,of)
514 
515  end select plasticitytype
516 
517  do i=1,3; do j=1,3
518  dlp_dfi(i,j,1:3,1:3) = matmul(matmul(fi,s),transpose(dlp_dmp(i,j,1:3,1:3))) + &
519  matmul(matmul(fi,dlp_dmp(i,j,1:3,1:3)),s)
520  dlp_ds(i,j,1:3,1:3) = matmul(matmul(transpose(fi),fi),dlp_dmp(i,j,1:3,1:3)) ! ToDo: @PS: why not: dLp_dMp:(FiT Fi)
521  enddo; enddo
522 
523 end subroutine constitutive_lpanditstangents
524 
525 
526 !--------------------------------------------------------------------------------------------------
528 ! ToDo: MD: S is Mi?
529 !--------------------------------------------------------------------------------------------------
530 subroutine constitutive_lianditstangents(Li, dLi_dS, dLi_dFi, &
531  S, Fi, ipc, ip, el)
532 
533  integer, intent(in) :: &
534  ipc, & !< component-ID of integration point
535  ip, & !< integration point
536  el
537  real(preal), intent(in), dimension(3,3) :: &
538  s
539  real(preal), intent(in), dimension(3,3) :: &
540  fi
541  real(preal), intent(out), dimension(3,3) :: &
542  li
543  real(preal), intent(out), dimension(3,3,3,3) :: &
544  dli_ds, & !< derivative of Li with respect to S
545  dli_dfi
546 
547  real(preal), dimension(3,3) :: &
548  my_li, & !< intermediate velocity gradient
549  fiinv, &
550  temp_33
551  real(preal), dimension(3,3,3,3) :: &
552  my_dli_ds
553  real(preal) :: &
554  detfi
555  integer :: &
556  k, i, j, &
557  instance, of
558 
559  li = 0.0_preal
560  dli_ds = 0.0_preal
561  dli_dfi = 0.0_preal
562 
563  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
564  case (plasticity_isotropic_id) plasticitytype
565  of = material_phasememberat(ipc,ip,el)
566  instance = phase_plasticityinstance(material_phaseat(ipc,el))
567  call plastic_isotropic_lianditstangent(my_li, my_dli_ds, s ,instance,of)
568  case default plasticitytype
569  my_li = 0.0_preal
570  my_dli_ds = 0.0_preal
571  end select plasticitytype
572 
573  li = li + my_li
574  dli_ds = dli_ds + my_dli_ds
575 
576  kinematicsloop: do k = 1, phase_nkinematics(material_phaseat(ipc,el))
577  kinematicstype: select case (phase_kinematics(k,material_phaseat(ipc,el)))
578  case (kinematics_cleavage_opening_id) kinematicstype
579  call kinematics_cleavage_opening_lianditstangent(my_li, my_dli_ds, s, ipc, ip, el)
580  case (kinematics_slipplane_opening_id) kinematicstype
581  call kinematics_slipplane_opening_lianditstangent(my_li, my_dli_ds, s, ipc, ip, el)
582  case (kinematics_thermal_expansion_id) kinematicstype
583  call kinematics_thermal_expansion_lianditstangent(my_li, my_dli_ds, ipc, ip, el)
584  case default kinematicstype
585  my_li = 0.0_preal
586  my_dli_ds = 0.0_preal
587  end select kinematicstype
588  li = li + my_li
589  dli_ds = dli_ds + my_dli_ds
590  enddo kinematicsloop
591 
592  fiinv = math_inv33(fi)
593  detfi = math_det33(fi)
594  li = matmul(matmul(fi,li),fiinv)*detfi
595  temp_33 = matmul(fiinv,li)
596 
597  do i = 1,3; do j = 1,3
598  dli_ds(1:3,1:3,i,j) = matmul(matmul(fi,dli_ds(1:3,1:3,i,j)),fiinv)*detfi
599  dli_dfi(1:3,1:3,i,j) = dli_dfi(1:3,1:3,i,j) + li*fiinv(j,i)
600  dli_dfi(1:3,i,1:3,j) = dli_dfi(1:3,i,1:3,j) + math_i3*temp_33(j,i) + li*fiinv(j,i)
601  enddo; enddo
602 
603 end subroutine constitutive_lianditstangents
604 
605 
606 !--------------------------------------------------------------------------------------------------
608 !--------------------------------------------------------------------------------------------------
609 pure function constitutive_initialfi(ipc, ip, el)
610 
611  integer, intent(in) :: &
612  ipc, & !< component-ID of integration point
613  ip, & !< integration point
614  el
615  real(preal), dimension(3,3) :: &
616  constitutive_initialfi
617  integer :: &
618  k
619  integer :: &
620  phase, &
621  homog, offset
622 
623  constitutive_initialfi = math_i3
624  phase = material_phaseat(ipc,el)
625 
626  kinematicsloop: do k = 1, phase_nkinematics(phase)
627  kinematicstype: select case (phase_kinematics(k,phase))
628  case (kinematics_thermal_expansion_id) kinematicstype
629  homog = material_homogenizationat(el)
630  offset = thermalmapping(homog)%p(ip,el)
631  constitutive_initialfi = &
632  constitutive_initialfi + kinematics_thermal_expansion_initialstrain(homog,phase,offset)
633  end select kinematicstype
634  enddo kinematicsloop
635 
636 end function constitutive_initialfi
637 
638 
639 !--------------------------------------------------------------------------------------------------
643 !--------------------------------------------------------------------------------------------------
644 subroutine constitutive_sanditstangents(S, dS_dFe, dS_dFi, Fe, Fi, ipc, ip, el)
645 
646  integer, intent(in) :: &
647  ipc, & !< component-ID of integration point
648  ip, & !< integration point
649  el
650  real(preal), intent(in), dimension(3,3) :: &
651  fe, & !< elastic deformation gradient
652  fi
653  real(preal), intent(out), dimension(3,3) :: &
654  s
655  real(preal), intent(out), dimension(3,3,3,3) :: &
656  ds_dfe, & !< derivative of 2nd P-K stress with respect to elastic deformation gradient
657  ds_dfi
658 
659  call constitutive_hooke_sanditstangents(s, ds_dfe, ds_dfi, fe, fi, ipc, ip, el)
660 
661 
662 end subroutine constitutive_sanditstangents
663 
664 
665 !--------------------------------------------------------------------------------------------------
668 !--------------------------------------------------------------------------------------------------
669 subroutine constitutive_hooke_sanditstangents(S, dS_dFe, dS_dFi, &
670  Fe, Fi, ipc, ip, el)
671 
672  integer, intent(in) :: &
673  ipc, & !< component-ID of integration point
674  ip, & !< integration point
675  el
676  real(pReal), intent(in), dimension(3,3) :: &
677  Fe, & !< elastic deformation gradient
678  Fi
679  real(pReal), intent(out), dimension(3,3) :: &
680  S
681  real(pReal), intent(out), dimension(3,3,3,3) :: &
682  dS_dFe, & !< derivative of 2nd P-K stress with respect to elastic deformation gradient
683  dS_dFi
684  real(pReal), dimension(3,3) :: E
685  real(pReal), dimension(3,3,3,3) :: C
686  integer :: &
687  ho, & !< homogenization
688  d
689  integer :: &
690  i, j
691 
693  c = math_66tosym3333(constitutive_homogenizedc(ipc,ip,el))
694 
695  degradationloop: do d = 1, phase_nstiffnessdegradations(material_phaseat(ipc,el))
696  degradationtype: select case(phase_stiffnessdegradation(d,material_phaseat(ipc,el)))
697  case (stiffness_degradation_damage_id) degradationtype
698  c = c * damage(ho)%p(damagemapping(ho)%p(ip,el))**2
699  end select degradationtype
700  enddo degradationloop
701 
702  e = 0.5_preal*(matmul(transpose(fe),fe)-math_i3)
703  s = math_mul3333xx33(c,matmul(matmul(transpose(fi),e),fi))
704 
705  do i =1, 3;do j=1,3
706  ds_dfe(i,j,1:3,1:3) = matmul(fe,matmul(matmul(fi,c(i,j,1:3,1:3)),transpose(fi)))
707  ds_dfi(i,j,1:3,1:3) = 2.0_preal*matmul(matmul(e,fi),c(i,j,1:3,1:3))
708  enddo; enddo
709 
710 end subroutine constitutive_hooke_sanditstangents
711 
712 
713 !--------------------------------------------------------------------------------------------------
715 !--------------------------------------------------------------------------------------------------
716 subroutine constitutive_collectdotstate(S, FArray, Fi, FpArray, subdt, ipc, ip, el)
717 
718  integer, intent(in) :: &
719  ipc, & !< component-ID of integration point
720  ip, & !< integration point
721  el
722  real(preal), intent(in) :: &
723  subdt
724  real(preal), intent(in), dimension(3,3,homogenization_maxNgrains,discretization_nIP,discretization_nElem) :: &
725  farray, & !< elastic deformation gradient
726  fparray
727  real(preal), intent(in), dimension(3,3) :: &
728  fi
729  real(preal), intent(in), dimension(3,3) :: &
730  s
731  real(preal), dimension(3,3) :: &
732  mp
733  integer :: &
734  ho, & !< homogenization
735  tme, & !< thermal member position
736  i, & !< counter in source loop
737  instance, of
738 
740  tme = thermalmapping(ho)%p(ip,el)
741  of = material_phasememberat(ipc,ip,el)
742  instance = phase_plasticityinstance(material_phaseat(ipc,el))
743 
744  mp = matmul(matmul(transpose(fi),fi),s)
745 
746  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
747 
748  case (plasticity_isotropic_id) plasticitytype
749  call plastic_isotropic_dotstate (mp,instance,of)
750 
751  case (plasticity_phenopowerlaw_id) plasticitytype
752  call plastic_phenopowerlaw_dotstate(mp,instance,of)
753 
754  case (plasticity_kinehardening_id) plasticitytype
755  call plastic_kinehardening_dotstate(mp,instance,of)
756 
757  case (plasticity_dislotwin_id) plasticitytype
758  call plastic_dislotwin_dotstate (mp,temperature(ho)%p(tme),instance,of)
759 
760  case (plasticity_disloucla_id) plasticitytype
761  call plastic_disloucla_dotstate (mp,temperature(ho)%p(tme),instance,of)
762 
763  case (plasticity_nonlocal_id) plasticitytype
764  call plastic_nonlocal_dotstate (mp,farray,fparray,temperature(ho)%p(tme),subdt, &
765  instance,of,ip,el)
766  end select plasticitytype
767 
768  sourceloop: do i = 1, phase_nsources(material_phaseat(ipc,el))
769 
770  sourcetype: select case (phase_source(i,material_phaseat(ipc,el)))
771 
772  case (source_damage_anisobrittle_id) sourcetype
773  call source_damage_anisobrittle_dotstate (s, ipc, ip, el)
774 
775  case (source_damage_isoductile_id) sourcetype
776  call source_damage_isoductile_dotstate ( ipc, ip, el)
777 
778  case (source_damage_anisoductile_id) sourcetype
779  call source_damage_anisoductile_dotstate ( ipc, ip, el)
780 
781  case (source_thermal_externalheat_id) sourcetype
783 
784  end select sourcetype
785 
786  enddo sourceloop
787 
788 end subroutine constitutive_collectdotstate
789 
790 
791 !--------------------------------------------------------------------------------------------------
794 !--------------------------------------------------------------------------------------------------
795 subroutine constitutive_collectdeltastate(S, Fe, Fi, ipc, ip, el)
796 
797  integer, intent(in) :: &
798  ipc, & !< component-ID of integration point
799  ip, & !< integration point
800  el
801  real(preal), intent(in), dimension(3,3) :: &
802  s, & !< 2nd Piola Kirchhoff stress
803  fe, & !< elastic deformation gradient
804  fi
805  real(preal), dimension(3,3) :: &
806  mp
807  integer :: &
808  i, &
809  instance, of
810 
811  mp = matmul(matmul(transpose(fi),fi),s)
812  of = material_phasememberat(ipc,ip,el)
813  instance = phase_plasticityinstance(material_phaseat(ipc,el))
814 
815  plasticitytype: select case (phase_plasticity(material_phaseat(ipc,el)))
816 
817  case (plasticity_kinehardening_id) plasticitytype
818  call plastic_kinehardening_deltastate(mp,instance,of)
819 
820  case (plasticity_nonlocal_id) plasticitytype
821  call plastic_nonlocal_deltastate(mp,instance,of,ip,el)
822 
823  end select plasticitytype
824 
825  sourceloop: do i = 1, phase_nsources(material_phaseat(ipc,el))
826 
827  sourcetype: select case (phase_source(i,material_phaseat(ipc,el)))
828 
829  case (source_damage_isobrittle_id) sourcetype
830  call source_damage_isobrittle_deltastate (constitutive_homogenizedc(ipc,ip,el), fe, &
831  ipc, ip, el)
832 
833  end select sourcetype
834 
835  enddo sourceloop
836 
837 end subroutine constitutive_collectdeltastate
838 
839 
840 !--------------------------------------------------------------------------------------------------
842 !--------------------------------------------------------------------------------------------------
843 subroutine constitutive_results
844 
845  integer :: p
846  character(len=pStringLen) :: group
847  do p=1,size(config_name_phase)
848  group = trim('current/constituent')//'/'//trim(config_name_phase(p))
850 
851  group = trim(group)//'/plastic'
852 
854  select case(phase_plasticity(p))
855 
857  call plastic_isotropic_results(phase_plasticityinstance(p),group)
858 
860  call plastic_phenopowerlaw_results(phase_plasticityinstance(p),group)
861 
863  call plastic_kinehardening_results(phase_plasticityinstance(p),group)
864 
866  call plastic_dislotwin_results(phase_plasticityinstance(p),group)
867 
869  call plastic_disloucla_results(phase_plasticityinstance(p),group)
870 
872  call plastic_nonlocal_results(phase_plasticityinstance(p),group)
873  end select
874 
875  enddo
876 
877 end subroutine constitutive_results
878 
879 end module constitutive
material::thermalmapping
type(thomogmapping), dimension(:), allocatable, public thermalmapping
mapping for thermal state/fields
Definition: material.f90:170
material::sourcestate
type(tsourcestate), dimension(:), allocatable, public sourcestate
Definition: material.f90:139
source_damage_isoductile::source_damage_isoductile_dotstate
subroutine, public source_damage_isoductile_dotstate(ipc, ip, el)
calculates derived quantities from state
Definition: source_damage_isoDuctile.f90:108
material::material_phaseat
integer, dimension(:,:), allocatable, public, protected material_phaseat
phase ID of each element
Definition: material.f90:132
kinematics_thermal_expansion::kinematics_thermal_expansion_lianditstangent
subroutine, public kinematics_thermal_expansion_lianditstangent(Li, dLi_dTstar, ipc, ip, el)
contains the constitutive equation for calculating the velocity gradient
Definition: kinematics_thermal_expansion.f90:112
kinematics_cleavage_opening::kinematics_cleavage_opening_init
subroutine, public kinematics_cleavage_opening_init
module initialization
Definition: kinematics_cleavage_opening.f90:51
source_damage_isobrittle
material subroutine incoprorating isotropic brittle damage source mechanism
Definition: source_damage_isoBrittle.f90:11
rotations
rotation storage and conversion
Definition: rotations.f90:53
material::source_damage_isoductile_id
@, public source_damage_isoductile_id
Definition: material.f90:87
source_damage_isoductile
material subroutine incoprorating isotropic ductile damage source mechanism
Definition: source_damage_isoDuctile.f90:11
material::damagemapping
type(thomogmapping), dimension(:), allocatable, public damagemapping
mapping for damage state/fields
Definition: material.f90:170
lattice::lattice_c66
real(preal), dimension(:,:,:), allocatable, public, protected lattice_c66
Definition: lattice.f90:404
kinematics_thermal_expansion::kinematics_thermal_expansion_initialstrain
pure real(preal) function, dimension(3, 3), public kinematics_thermal_expansion_initialstrain(homog, phase, offset)
report initial thermal strain based on current temperature deviation from reference
Definition: kinematics_thermal_expansion.f90:89
material::material_phasememberat
integer, dimension(:,:,:), allocatable, public, protected material_phasememberat
position of the element within its phase instance
Definition: material.f90:134
constitutive::constitutive_plasticity_maxsizedotstate
integer, public, protected constitutive_plasticity_maxsizedotstate
Definition: constitutive.f90:36
kinematics_cleavage_opening
material subroutine incorporating kinematics resulting from opening of cleavage planes
Definition: kinematics_cleavage_opening.f90:11
rotations::rotation
Definition: rotations.f90:63
source_thermal_externalheat::source_thermal_externalheat_dotstate
subroutine, public source_thermal_externalheat_dotstate(phase, of)
rate of change of state
Definition: source_thermal_externalheat.f90:94
material::source_damage_isobrittle_id
@, public source_damage_isobrittle_id
Definition: material.f90:87
material::source_thermal_dissipation_id
@, public source_thermal_dissipation_id
Definition: material.f90:87
material::kinematics_thermal_expansion_id
@, public kinematics_thermal_expansion_id
Definition: material.f90:87
material::phase_plasticity
integer(kind(plasticity_undefined_id)), dimension(:), allocatable, public, protected phase_plasticity
plasticity of each phase
Definition: material.f90:92
source_thermal_dissipation
material subroutine for thermal source due to plastic dissipation
Definition: source_thermal_dissipation.f90:11
material::plasticity_isotropic_id
@, public plasticity_isotropic_id
Definition: material.f90:87
material::plasticity_dislotwin_id
@, public plasticity_dislotwin_id
Definition: material.f90:87
material::temperature
type(group_float), dimension(:), allocatable, public temperature
temperature field
Definition: material.f90:174
kinematics_thermal_expansion::kinematics_thermal_expansion_init
subroutine, public kinematics_thermal_expansion_init
module initialization
Definition: kinematics_thermal_expansion.f90:46
source_damage_anisobrittle::source_damage_anisobrittle_init
subroutine, public source_damage_anisobrittle_init
module initialization
Definition: source_damage_anisoBrittle.f90:61
source_damage_isoductile::source_damage_isoductile_init
subroutine, public source_damage_isoductile_init
module initialization
Definition: source_damage_isoDuctile.f90:52
config::config_name_phase
character(len=pstringlen), dimension(:), allocatable, public, protected config_name_phase
name of each phase
Definition: config.f90:34
material
Parses material config file, either solverJobName.materialConfig or material.config.
Definition: material.f90:11
config
Reads in the material configuration from file.
Definition: config.f90:13
material::phase_nkinematics
integer, dimension(:), allocatable, public, protected phase_nkinematics
number of kinematic mechanisms active in each phase
Definition: material.f90:113
geometry_plastic_nonlocal
Geometric information about the IP cells needed for the nonlocal.
Definition: geometry_plastic_nonlocal.f90:12
constitutive::constitutive_source_maxsizedotstate
integer, public, protected constitutive_source_maxsizedotstate
Definition: constitutive.f90:36
kinematics_thermal_expansion
material subroutine incorporating kinematics resulting from thermal expansion
Definition: kinematics_thermal_expansion.f90:10
prec
setting precision for real and int type
Definition: prec.f90:13
source_damage_anisoductile::source_damage_anisoductile_init
subroutine, public source_damage_anisoductile_init
module initialization
Definition: source_damage_anisoDuctile.f90:54
math::math_det33
real(preal) pure function math_det33(m)
determinant of a 3x3 matrix
Definition: math.f90:623
math::math_66tosym3333
pure real(preal) function, dimension(3, 3, 3, 3) math_66tosym3333(m66, weighted)
convert 66 matrix into symmetric 3x3x3x3 matrix
Definition: math.f90:806
math::math_mul3333xx33
pure real(preal) function, dimension(3, 3) math_mul3333xx33(A, B)
matrix double contraction 3333x33 = 33 (ijkl,kl)
Definition: math.f90:368
kinematics_slipplane_opening::kinematics_slipplane_opening_init
subroutine, public kinematics_slipplane_opening_init
module initialization
Definition: kinematics_slipplane_opening.f90:53
discretization
spatial discretization
Definition: discretization.f90:9
kinematics_slipplane_opening::kinematics_slipplane_opening_lianditstangent
subroutine, public kinematics_slipplane_opening_lianditstangent(Ld, dLd_dTstar, S, ipc, ip, el)
contains the constitutive equation for calculating the velocity gradient
Definition: kinematics_slipplane_opening.f90:117
kinematics_slipplane_opening
material subroutine incorporating kinematics resulting from opening of slip planes
Definition: kinematics_slipplane_opening.f90:11
material::source_thermal_externalheat_id
@, public source_thermal_externalheat_id
Definition: material.f90:87
source_damage_isobrittle::source_damage_isobrittle_deltastate
subroutine, public source_damage_isobrittle_deltastate(C, Fe, ipc, ip, el)
calculates derived quantities from state
Definition: source_damage_isoBrittle.f90:109
material::plasticity_phenopowerlaw_id
@, public plasticity_phenopowerlaw_id
Definition: material.f90:87
io
input/output functions, partly depending on chosen solver
Definition: IO.f90:12
material::phase_plasticityinstance
integer, dimension(:), allocatable, public, protected phase_plasticityinstance
instance of particular plasticity of each phase
Definition: material.f90:113
source_damage_anisoductile
material subroutine incorporating anisotropic ductile damage source mechanism
Definition: source_damage_anisoDuctile.f90:11
prec::preal
integer, parameter preal
number with 15 significant digits, up to 1e+-307 (typically 64 bit)
Definition: prec.f90:20
debug
Reading in and interpretating the debugging settings for the various modules.
Definition: debug.f90:12
material::kinematics_slipplane_opening_id
@, public kinematics_slipplane_opening_id
Definition: material.f90:87
material::phase_kinematics
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_kinematics
active kinematic mechanisms of each phase
Definition: material.f90:105
material::source_damage_anisobrittle_id
@, public source_damage_anisobrittle_id
Definition: material.f90:87
material::phase_nstiffnessdegradations
integer, dimension(:), allocatable, public, protected phase_nstiffnessdegradations
number of stiffness degradation mechanisms active in each phase
Definition: material.f90:113
results::results_addgroup
integer(hid_t) function, public results_addgroup(groupName)
adds a new group to the results file
Definition: results.f90:154
source_damage_anisobrittle
material subroutine incorporating anisotropic brittle damage source mechanism
Definition: source_damage_anisoBrittle.f90:11
geometry_plastic_nonlocal::geometry_plastic_nonlocal_disable
subroutine geometry_plastic_nonlocal_disable
Free memory used by variables only needed by plastic_nonlocal.
Definition: geometry_plastic_nonlocal.f90:98
source_damage_isobrittle::source_damage_isobrittle_init
subroutine, public source_damage_isobrittle_init
module initialization
Definition: source_damage_isoBrittle.f90:53
constitutive
elasticity, plasticity, internal microstructure state
Definition: constitutive.f90:10
lattice
contains lattice structure definitions including Schmid matrices for slip, twin, trans,
Definition: lattice.f90:13
results
Definition: results.f90:11
material::stiffness_degradation_damage_id
@, public stiffness_degradation_damage_id
Definition: material.f90:87
material::plasticity_disloucla_id
@, public plasticity_disloucla_id
Definition: material.f90:87
material::material_homogenizationat
integer, dimension(:), allocatable, public, protected material_homogenizationat
homogenization ID of each element (copy of discretization_homogenizationAt)
Definition: material.f90:128
source_thermal_externalheat
material subroutine for variable heat source
Definition: source_thermal_externalheat.f90:11
material::material_nphase
integer, public, protected material_nphase
number of phases
Definition: material.f90:101
kinematics_cleavage_opening::kinematics_cleavage_opening_lianditstangent
subroutine, public kinematics_cleavage_opening_lianditstangent(Ld, dLd_dTstar, S, ipc, ip, el)
contains the constitutive equation for calculating the velocity gradient
Definition: kinematics_cleavage_opening.f90:105
material::plasticstate
type(tplasticstate), dimension(:), allocatable, public plasticstate
Definition: material.f90:137
math
Mathematical library, including random number generation and tensor representations.
Definition: math.f90:12
material::kinematics_cleavage_opening_id
@, public kinematics_cleavage_opening_id
Definition: material.f90:87
material::plasticity_nonlocal_id
@, public plasticity_nonlocal_id
Definition: material.f90:87
material::plasticity_kinehardening_id
@, public plasticity_kinehardening_id
Definition: material.f90:87
material::phase_source
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_source
active sources mechanisms of each phase
Definition: material.f90:105
results::results_closegroup
subroutine, public results_closegroup(group_id)
close a group
Definition: results.f90:166
source_damage_anisobrittle::source_damage_anisobrittle_dotstate
subroutine, public source_damage_anisobrittle_dotstate(S, ipc, ip, el)
calculates derived quantities from state
Definition: source_damage_anisoBrittle.f90:133
material::phase_stiffnessdegradation
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_stiffnessdegradation
active stiffness degradation mechanisms of each phase
Definition: material.f90:105
material::phase_nsources
integer, dimension(:), allocatable, public, protected phase_nsources
number of source mechanisms active in each phase
Definition: material.f90:113
material::damage
type(group_float), dimension(:), allocatable, public damage
damage field
Definition: material.f90:174
math::math_inv33
pure real(preal) function, dimension(3, 3) math_inv33(A)
Cramer inversion of 3x3 matrix (function)
Definition: math.f90:435
source_damage_anisoductile::source_damage_anisoductile_dotstate
subroutine, public source_damage_anisoductile_dotstate(ipc, ip, el)
calculates derived quantities from state
Definition: source_damage_anisoDuctile.f90:115
numerics
Managing of parameters related to numerics.
Definition: numerics.f90:10
material::source_damage_anisoductile_id
@, public source_damage_anisoductile_id
Definition: material.f90:87
material::plasticity_none_id
@, public plasticity_none_id
Definition: material.f90:87
source_thermal_externalheat::source_thermal_externalheat_init
subroutine, public source_thermal_externalheat_init
module initialization
Definition: source_thermal_externalheat.f90:49
source_thermal_dissipation::source_thermal_dissipation_init
subroutine, public source_thermal_dissipation_init
module initialization
Definition: source_thermal_dissipation.f90:45
math::math_i3
real(preal), dimension(3, 3), parameter math_i3
3x3 Identity
Definition: math.f90:32