DAMASK_EICMD/src/plastic_none.f90

50 lines
1.6 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
!--------------------------------------------------------------------------------------------------
module plastic_none
use material
use discretization
use debug
implicit none
private
public :: &
plastic_none_init
contains
!--------------------------------------------------------------------------------------------------
!> @brief module initialization
!> @details reads in material parameters, allocates arrays, and does sanity checks
!--------------------------------------------------------------------------------------------------
subroutine plastic_none_init
2019-03-12 04:37:44 +05:30
integer :: &
2019-01-06 04:25:10 +05:30
Ninstance, &
p, &
NipcMyPhase
2019-01-05 14:36:37 +05:30
write(6,'(/,a)') ' <<<+- plastic_'//PLASTICITY_NONE_label//' init -+>>>'
2019-01-06 04:25:10 +05:30
2019-03-12 04:37:44 +05:30
Ninstance = count(phase_plasticity == PLASTICITY_NONE_ID)
if (iand(debug_level(debug_constitutive),debug_levelBasic) /= 0) &
2019-01-06 04:25:10 +05:30
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance
2019-03-12 04:37:44 +05:30
do p = 1, size(phase_plasticity)
2019-01-06 04:25:10 +05:30
if (phase_plasticity(p) /= PLASTICITY_NONE_ID) cycle
2014-05-22 20:54:12 +05:30
NipcMyPhase = count(material_phaseAt == p) * discretization_nIP
2019-03-12 04:37:44 +05:30
call material_allocatePlasticState(p,NipcMyPhase,0,0,0, &
0,0,0)
plasticState(p)%sizePostResults = 0
2019-01-06 04:25:10 +05:30
enddo
end subroutine plastic_none_init
end module plastic_none