DAMASK_EICMD/src/constitutive_plastic_none.f90

52 lines
1.8 KiB
Fortran
Raw Normal View History

!--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!> @author Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
2019-01-06 04:25:10 +05:30
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Dummy plasticity for purely elastic material
!--------------------------------------------------------------------------------------------------
submodule(constitutive:constitutive_plastic) plastic_none
contains
!--------------------------------------------------------------------------------------------------
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
module function plastic_none_init() result(myPlasticity)
2020-08-15 19:32:10 +05:30
logical, dimension(:), allocatable :: myPlasticity
integer :: &
Ninstance, &
p, &
NipcMyPhase
2020-08-15 19:32:10 +05:30
class(tNode), pointer :: &
phases, &
phase, &
pl
write(6,'(/,a)') ' <<<+- plastic_none init -+>>>'
phases => material_root%get('phase')
allocate(myPlasticity(phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get(p)
pl => phase%get('plasticity')
if(pl%get_asString('type') == 'none') myPlasticity(p) = .true.
enddo
2020-08-15 19:32:10 +05:30
Ninstance = count(myPlasticity)
2020-07-02 00:16:26 +05:30
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
2020-08-15 19:32:10 +05:30
if(Ninstance == 0) return
do p = 1, phases%length
phase => phases%get(p)
if(.not. myPlasticity(p)) cycle
NipcMyPhase = count(material_phaseAt == p) * discretization_nIP
2020-08-15 19:32:10 +05:30
call constitutive_allocateState(plasticState(p),NipcMyPhase,0,0,0)
enddo
2020-08-15 19:32:10 +05:30
end function plastic_none_init
end submodule plastic_none