|  | DAMASK with grid solvers
    Revision: v2.0.3-2204-gdb1f2151
    The Düsseldorf Advanced Material Simulation Kit with Grid Solvers |  | 
 
 
 
Go to the documentation of this file.    1 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_damage_isoDuctile.f90" 
    4 # 1 "/home/damask_user/GitLabCI_Pipeline_4301/DAMASK/src/source_damage_isoDuctile.f90" 
   23   integer,                       
dimension(:),           
allocatable :: &
 
   31     character(len=pStringLen), 
allocatable, 
dimension(:) :: &
 
   53   integer :: ninstance,sourceoffset,nipcmyphase,p
 
   54   character(len=pStringLen) :: extmsg = 
'' 
   60     write(6,
'(a16,1x,i5,/)') 
'# instances:',ninstance
 
   64   allocate(
param(ninstance))
 
   81     prm%N                 = 
config%getFloat(
'isoductile_ratesensitivity')
 
   82     prm%critPlasticStrain = 
config%getFloat(
'isoductile_criticalplasticstrain')
 
   85     if (prm%N                 <= 0.0_preal) extmsg = trim(extmsg)//
' isoductile_ratesensitivity' 
   86     if (prm%critPlasticStrain <= 0.0_preal) extmsg = trim(extmsg)//
' isoductile_criticalplasticstrain' 
   90     sourcestate(p)%p(sourceoffset)%atol = 
config%getFloat(
'isoductile_atol',defaultval=1.0e-3_preal)
 
   91     if(any(
sourcestate(p)%p(sourceoffset)%atol < 0.0_preal)) extmsg = trim(extmsg)//
' isoductile_atol' 
  109   integer, 
intent(in) :: &
 
  110     ipc, &                                                                                          !< component-ID of integration point
 
  111     ip, &                                                                                           !< integration point
 
  121   phase = material_phaseat(ipc,el)
 
  122   constituent = material_phasememberat(ipc,ip,el)
 
  124   homog = material_homogenizationat(el)
 
  125   damageoffset = damagemapping(homog)%p(ip,el)
 
  128   sourcestate(phase)%p(sourceoffset)%dotState(1,constituent) = &
 
  129     sum(plasticstate(phase)%slipRate(:,constituent))/(damage(homog)%p(damageoffset)**prm%N)/prm%critPlasticStrain
 
  140   integer, 
intent(in) :: &
 
  143   real(preal),  
intent(in) :: &
 
  145   real(preal),  
intent(out) :: &
 
  154   dlocalphidot_dphi = -sourcestate(phase)%p(sourceoffset)%state(1,constituent)
 
  156   localphidot = 1.0_preal &
 
  157               + dlocalphidot_dphi*phi
 
  167   integer,          
intent(in) :: phase
 
  168   character(len=*), 
intent(in) :: group
 
  174   outputsloop: 
do o = 1,
size(prm%output)
 
  175     select case(trim(prm%output(o)))
 
  176       case (
'isoductile_drivingforce')
 
  177         call results_writedataset(group,stt,
'tbd',
'driving force',
'tbd')
 
 
 
type(tsourcestate), dimension(:), allocatable, public sourcestate
subroutine, public source_damage_isoductile_dotstate(ipc, ip, el)
calculates derived quantities from state
integer, dimension(:,:), allocatable, public, protected material_phaseat
phase ID of each element
@, public source_damage_isoductile_id
material subroutine incoprorating isotropic ductile damage source mechanism
subroutine, public io_error(error_ID, el, ip, g, instance, ext_msg)
write error statements to standard out and terminate the Marc/spectral run with exit #9xxx
type(tpartitionedstringlist), dimension(:), allocatable, public, protected config_phase
integer, dimension(debug_maxntype+2), public, protected debug_level
subroutine, public source_damage_isoductile_results(phase, group)
writes results to HDF5 output file
character(len=pstringlen), dimension(0), parameter emptystringarray
subroutine, public source_damage_isoductile_init
module initialization
Parses material config file, either solverJobName.materialConfig or material.config.
Reads in the material configuration from file.
setting precision for real and int type
integer, dimension(:), allocatable source_damage_isoductile_instance
instance of damage source mechanism
integer, public, protected discretization_nip
input/output functions, partly depending on chosen solver
integer, parameter, public debug_levelbasic
integer, parameter preal
number with 15 significant digits, up to 1e+-307 (typically 64 bit)
Reading in and interpretating the debugging settings for the various modules.
subroutine, public material_allocatesourcestate(phase, of, NipcMyPhase, sizeState, sizeDotState, sizeDeltaState)
allocates the source state of a phase
type(tparameters), dimension(:), allocatable, private param
containers of constitutive parameters (len Ninstance)
subroutine, public source_damage_isoductile_getrateanditstangent(localphiDot, dLocalphiDot_dPhi, phi, phase, constituent)
returns local part of nonlocal damage driving force
container type for internal constitutive parameters
integer, parameter, public debug_constitutive
stores debug level for constitutive part of DAMASK bitwise coded
integer(kind(source_undefined_id)), dimension(:,:), allocatable, public, protected phase_source
active sources mechanisms of each phase
integer, dimension(:), allocatable, public, protected phase_nsources
number of source mechanisms active in each phase
character(len= *), parameter, public source_damage_isoductile_label
integer, dimension(:), allocatable source_damage_isoductile_offset
which source is my current damage mechanism?