prefix should be name of the module

poor substitute for namespace
This commit is contained in:
Martin Diehl 2020-09-13 10:39:17 +02:00
parent da0e16520c
commit b499578a95
41 changed files with 133 additions and 133 deletions

View File

@ -115,19 +115,19 @@ subroutine CPFEM_init
!------------------------------------------------------------------------------
! read numerical parameters and do sanity check
num_commercialFEM => numerics_root%get('commercialFEM',defaultVal=emptyDict)
num_commercialFEM => config_numerics%get('commercialFEM',defaultVal=emptyDict)
num%iJacoStiffness = num_commercialFEM%get_asInt('ijacostiffness',defaultVal=1)
if (num%iJacoStiffness < 1) call IO_error(301,ext_msg='iJacoStiffness')
!------------------------------------------------------------------------------
! read debug options
debug_CPFEM => debug_root%get('cpfem',defaultVal=emptyList)
debug_CPFEM => config_debug%get('cpfem',defaultVal=emptyList)
debugCPFEM%basic = debug_CPFEM%contains('basic')
debugCPFEM%extensive = debug_CPFEM%contains('extensive')
debugCPFEM%selective = debug_CPFEM%contains('selective')
debugCPFEM%element = debug_root%get_asInt('element',defaultVal = 1)
debugCPFEM%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
debugCPFEM%element = config_debug%get_asInt('element',defaultVal = 1)
debugCPFEM%ip = config_debug%get_asInt('integrationpoint',defaultVal = 1)
if(debugCPFEM%basic) then
write(6,'(a32,1x,6(i8,1x))') 'CPFEM_cs: ', shape(CPFEM_cs)

View File

@ -277,7 +277,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
if (.not. CPFEM_init_done) then
CPFEM_init_done = .true.
call CPFEM_initAll
debug_Marc => debug_root%get('marc',defaultVal=emptyList)
debug_Marc => config_debug%get('marc',defaultVal=emptyList)
debug_basic = debug_Marc%contains('basic')
endif

View File

@ -20,9 +20,9 @@ module config
private
class(tNode), pointer, public :: &
material_root, &
numerics_root, &
debug_root
config_material, &
config_numerics, &
config_debug
public :: &
config_init, &
@ -60,7 +60,7 @@ subroutine parse_material
if(.not. fileExists) call IO_error(100,ext_msg=fname)
endif
write(6,*) 'reading '//fname; flush(6)
material_root => parse_flow(to_flow(IO_read(fname)))
config_material => parse_flow(to_flow(IO_read(fname)))
end subroutine parse_material
@ -73,11 +73,11 @@ subroutine parse_numerics
logical :: fexist
numerics_root => emptyDict
config_numerics => emptyDict
inquire(file='numerics.yaml', exist=fexist)
if (fexist) then
write(6,*) 'reading numerics.yaml'; flush(6)
numerics_root => parse_flow(to_flow(IO_read('numerics.yaml')))
config_numerics => parse_flow(to_flow(IO_read('numerics.yaml')))
endif
end subroutine parse_numerics
@ -90,11 +90,11 @@ subroutine parse_debug
logical :: fexist
debug_root => emptyDict
config_debug => emptyDict
inquire(file='debug.yaml', exist=fexist)
fileExists: if (fexist) then
write(6,*) 'reading debug.yaml'; flush(6)
debug_root => parse_flow(to_flow(IO_read('debug.yaml')))
config_debug => parse_flow(to_flow(IO_read('debug.yaml')))
endif fileExists
end subroutine parse_debug
@ -106,7 +106,7 @@ end subroutine parse_debug
!--------------------------------------------------------------------------------------------------
subroutine config_deallocate
deallocate(material_root)
deallocate(config_material)
end subroutine config_deallocate

View File

@ -140,7 +140,7 @@ module constitutive
el !< current element number
end subroutine plastic_nonlocal_dotState
module subroutine source_damage_anisoBrittle_dotState(S, ipc, ip, el)
integer, intent(in) :: &
ipc, & !< component-ID of integration point
@ -212,7 +212,7 @@ module constitutive
real(pReal), dimension(3,3) :: &
initialStrain
end function kinematics_thermal_expansion_initialStrain
module subroutine plastic_nonlocal_updateCompatibility(orientation,instance,i,e)
integer, intent(in) :: &
instance, &
@ -269,7 +269,7 @@ module constitutive
Li !< thermal velocity gradient
real(pReal), intent(out), dimension(3,3,3,3) :: &
dLi_dTstar !< derivative of Li with respect to Tstar (4th-order tensor defined to be zero)
end subroutine kinematics_thermal_expansion_LiAndItsTangent
end subroutine kinematics_thermal_expansion_LiAndItsTangent
module subroutine plastic_kinehardening_deltaState(Mp,instance,of)
@ -303,7 +303,7 @@ module constitutive
module subroutine plastic_results
end subroutine plastic_results
module subroutine damage_results
end subroutine damage_results
@ -339,7 +339,7 @@ module constitutive
real(pReal), intent(in), dimension(3,3) :: &
F, & !< elastic deformation gradient
Fp !< plastic deformation gradient
end subroutine constitutive_plastic_dependentState
end subroutine constitutive_plastic_dependentState
end interface constitutive_dependentState
@ -356,7 +356,7 @@ module constitutive
end type tDebugOptions
type(tDebugOptions) :: debugConstitutive
public :: &
constitutive_init, &
constitutive_homogenizedC, &
@ -379,7 +379,7 @@ contains
!--------------------------------------------------------------------------------------------------
!> @brief Initialze constitutive models for individual physics
!> @brief Initialze constitutive models for individual physics
!--------------------------------------------------------------------------------------------------
subroutine constitutive_init
@ -394,17 +394,17 @@ subroutine constitutive_init
elastic, &
stiffDegradation
debug_constitutive => debug_root%get('constitutive', defaultVal=emptyList)
debugConstitutive%basic = debug_constitutive%contains('basic')
debugConstitutive%extensive = debug_constitutive%contains('extensive')
debug_constitutive => config_debug%get('constitutive', defaultVal=emptyList)
debugConstitutive%basic = debug_constitutive%contains('basic')
debugConstitutive%extensive = debug_constitutive%contains('extensive')
debugConstitutive%selective = debug_constitutive%contains('selective')
debugConstitutive%element = debug_root%get_asInt('element',defaultVal = 1)
debugConstitutive%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
debugConstitutive%grain = debug_root%get_asInt('grain',defaultVal = 1)
debugConstitutive%element = config_debug%get_asInt('element',defaultVal = 1)
debugConstitutive%ip = config_debug%get_asInt('integrationpoint',defaultVal = 1)
debugConstitutive%grain = config_debug%get_asInt('grain',defaultVal = 1)
!-------------------------------------------------------------------------------------------------
! initialize elasticity (hooke) !ToDO: Maybe move to elastic submodule along with function homogenizedC?
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(phase_elasticity(phases%length), source = ELASTICITY_undefined_ID)
allocate(phase_elasticityInstance(phases%length), source = 0)
allocate(phase_NstiffnessDegradations(phases%length),source=0)
@ -472,7 +472,7 @@ end subroutine constitutive_init
!--------------------------------------------------------------------------------------------------
module function source_active(source_label,src_length) result(active_source)
character(len=*), intent(in) :: source_label !< name of source mechanism
character(len=*), intent(in) :: source_label !< name of source mechanism
integer, intent(in) :: src_length !< max. number of sources in system
logical, dimension(:,:), allocatable :: active_source
@ -480,10 +480,10 @@ module function source_active(source_label,src_length) result(active_source)
phases, &
phase, &
sources, &
src
src
integer :: p,s
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(active_source(src_length,phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get(p)
@ -512,10 +512,10 @@ module function kinematics_active(kinematics_label,kinematics_length) result(ac
phases, &
phase, &
kinematics, &
kinematics_type
kinematics_type
integer :: p,k
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(active_kinematics(kinematics_length,phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get(p)
@ -528,7 +528,7 @@ module function kinematics_active(kinematics_label,kinematics_length) result(ac
end function kinematics_active
!--------------------------------------------------------------------------------------------------
!> @brief returns the homogenize elasticity matrix

View File

@ -117,7 +117,7 @@ module subroutine damage_init
sources, &
kinematics
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(sourceState (phases%length))
allocate(phase_Nsources(phases%length),source = 0) ! same for kinematics

View File

@ -198,7 +198,7 @@ module subroutine plastic_init
integer :: p
class(tNode), pointer :: phases
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(plasticState(phases%length))
allocate(phase_plasticity(phases%length),source = PLASTICITY_undefined_ID)
@ -235,7 +235,7 @@ module function plastic_active(plastic_label) result(active_plastic)
pl
integer :: p
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(active_plastic(phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get(p)

View File

@ -112,7 +112,7 @@ module function plastic_disloTungsten_init() result(myPlasticity)
allocate(dotState(Ninstance))
allocate(dependentState(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -165,7 +165,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
allocate(dotState(Ninstance))
allocate(dependentState(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -83,7 +83,7 @@ module function plastic_isotropic_init() result(myPlasticity)
allocate(state(Ninstance))
allocate(dotState(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -92,7 +92,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
allocate(dotState(Ninstance))
allocate(deltaState(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -26,7 +26,7 @@ module function plastic_none_init() result(myPlasticity)
write(6,'(/,a)') ' <<<+- plastic_none init -+>>>'
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(myPlasticity(phases%length), source = .false. )
do p = 1, phases%length
phase => phases%get(p)

View File

@ -209,7 +209,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
allocate(deltaState(Ninstance))
allocate(microstructure(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -101,7 +101,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
allocate(state(Ninstance))
allocate(dotState(Ninstance))
phases => material_root%get('phase')
phases => config_material%get('phase')
i = 0
do p = 1, phases%length
phase => phases%get(p)

View File

@ -150,13 +150,13 @@ subroutine crystallite_init
write(6,'(/,a)') ' <<<+- crystallite init -+>>>'
debug_crystallite => debug_root%get('crystallite', defaultVal=emptyList)
debug_crystallite => config_debug%get('crystallite', defaultVal=emptyList)
debugCrystallite%basic = debug_crystallite%contains('basic')
debugCrystallite%extensive = debug_crystallite%contains('extensive')
debugCrystallite%selective = debug_crystallite%contains('selective')
debugCrystallite%element = debug_root%get_asInt('element', defaultVal=1)
debugCrystallite%ip = debug_root%get_asInt('integrationpoint', defaultVal=1)
debugCrystallite%grain = debug_root%get_asInt('grain', defaultVal=1)
debugCrystallite%element = config_debug%get_asInt('element', defaultVal=1)
debugCrystallite%ip = config_debug%get_asInt('integrationpoint', defaultVal=1)
debugCrystallite%grain = config_debug%get_asInt('grain', defaultVal=1)
cMax = homogenization_maxNgrains
iMax = discretization_nIP
@ -189,7 +189,7 @@ subroutine crystallite_init
allocate(crystallite_requested(cMax,iMax,eMax), source=.false.)
allocate(crystallite_converged(cMax,iMax,eMax), source=.true.)
num_crystallite => numerics_root%get('crystallite',defaultVal=emptyDict)
num_crystallite => config_numerics%get('crystallite',defaultVal=emptyDict)
num%subStepMinCryst = num_crystallite%get_asFloat ('subStepMin', defaultVal=1.0e-3_pReal)
num%subStepSizeCryst = num_crystallite%get_asFloat ('subStepSize', defaultVal=0.25_pReal)
@ -236,7 +236,7 @@ subroutine crystallite_init
call IO_error(301,ext_msg='integrator')
end select
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(output_constituent(phases%length))
do c = 1, phases%length

View File

@ -53,14 +53,14 @@ subroutine damage_local_init
!----------------------------------------------------------------------------------------------
! read numerics parameter and do sanity check
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
num_generic => config_numerics%get('generic',defaultVal=emptyDict)
num%residualStiffness = num_generic%get_asFloat('residualStiffness', defaultVal=1.0e-6_pReal)
if (num%residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
Ninstance = count(damage_type == DAMAGE_local_ID)
allocate(param(Ninstance))
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, material_homogenization%length
if (damage_type(h) /= DAMAGE_LOCAL_ID) cycle
homog => material_homogenization%get(h)

View File

@ -57,13 +57,13 @@ subroutine damage_nonlocal_init
!------------------------------------------------------------------------------------
! read numerics parameter
num_generic => numerics_root%get('generic',defaultVal= emptyDict)
num_generic => config_numerics%get('generic',defaultVal= emptyDict)
num%charLength = num_generic%get_asFloat('charLength',defaultVal=1.0_pReal)
Ninstance = count(damage_type == DAMAGE_nonlocal_ID)
allocate(param(Ninstance))
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, material_homogenization%length
if (damage_type(h) /= DAMAGE_NONLOCAL_ID) cycle
homog => material_homogenization%get(h)

View File

@ -114,7 +114,7 @@ program DAMASK_grid
!-------------------------------------------------------------------------------------------------
! reading field paramters from numerics file and do sanity checks
num_grid => numerics_root%get('grid', defaultVal=emptyDict)
num_grid => config_numerics%get('grid', defaultVal=emptyDict)
stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10)
maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3)
@ -124,7 +124,7 @@ program DAMASK_grid
!--------------------------------------------------------------------------------------------------
! assign mechanics solver depending on selected type
debug_grid => debug_root%get('grid',defaultVal=emptyList)
debug_grid => config_debug%get('grid',defaultVal=emptyList)
select case (trim(num_grid%get_asString('solver', defaultVal = 'Basic')))
case ('Basic')
mech_init => grid_mech_spectral_basic_init

View File

@ -93,8 +93,8 @@ subroutine discretization_grid_init(restart)
!-------------------------------------------------------------------------------------------------
! debug parameters
debug_element = debug_root%get_asInt('element',defaultVal=1)
debug_ip = debug_root%get_asInt('integrationpoint',defaultVal=1)
debug_element = config_debug%get_asInt('element',defaultVal=1)
debug_ip = config_debug%get_asInt('integrationpoint',defaultVal=1)
!--------------------------------------------------------------------------------------------------
! general discretization

View File

@ -84,12 +84,12 @@ subroutine grid_damage_spectral_init
!-------------------------------------------------------------------------------------------------
! read numerical parameters and do sanity checks
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%itmax = num_grid%get_asInt ('itmax',defaultVal=250)
num%eps_damage_atol = num_grid%get_asFloat ('eps_damage_atol',defaultVal=1.0e-2_pReal)
num%eps_damage_rtol = num_grid%get_asFloat ('eps_damage_rtol',defaultVal=1.0e-6_pReal)
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
num_generic => config_numerics%get('generic',defaultVal=emptyDict)
num%residualStiffness = num_generic%get_asFloat('residualStiffness', defaultVal=1.0e-6_pReal)
if (num%residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')

View File

@ -126,12 +126,12 @@ subroutine grid_mech_FEM_init
!-----------------------------------------------------------------------------------------------
! debugging options
debug_grid => debug_root%get('grid', defaultVal=emptyList)
debug_grid => config_debug%get('grid', defaultVal=emptyList)
debugRotation = debug_grid%contains('rotation')
!-------------------------------------------------------------------------------------------------
! read numerical parameter and do sanity checks
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)
num%eps_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.0e-4_pReal)
num%eps_stress_atol = num_grid%get_asFloat ('eps_stress_atol', defaultVal=1.0e3_pReal)

View File

@ -120,12 +120,12 @@ subroutine grid_mech_spectral_basic_init
!-------------------------------------------------------------------------------------------------
! debugging options
debug_grid => debug_root%get('grid', defaultVal=emptyList)
debug_grid => config_debug%get('grid', defaultVal=emptyList)
debugRotation = debug_grid%contains('rotation')
!-------------------------------------------------------------------------------------------------
! read numerical parameters and do sanity checks
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)

View File

@ -130,12 +130,12 @@ subroutine grid_mech_spectral_polarisation_init
!------------------------------------------------------------------------------------------------
! debugging options
debug_grid => debug_root%get('grid',defaultVal=emptyList)
debug_grid => config_debug%get('grid',defaultVal=emptyList)
debugRotation = debug_grid%contains('rotation')
!-------------------------------------------------------------------------------------------------
! read numerical parameters
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
num%eps_div_atol = num_grid%get_asFloat ('eps_div_atol', defaultVal=1.0e-4_pReal)

View File

@ -81,7 +81,7 @@ subroutine grid_thermal_spectral_init
!-------------------------------------------------------------------------------------------------
! read numerical parameter and do sanity checks
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%itmax = num_grid%get_asInt ('itmax', defaultVal=250)
num%eps_thermal_atol = num_grid%get_asFloat ('eps_thermal_atol',defaultVal=1.0e-2_pReal)
num%eps_thermal_rtol = num_grid%get_asFloat ('eps_thermal_rtol',defaultVal=1.0e-6_pReal)

View File

@ -207,7 +207,7 @@ subroutine spectral_utilities_init
!--------------------------------------------------------------------------------------------------
! set debugging parameters
debug_grid => debug_root%get('grid',defaultVal=emptyList)
debug_grid => config_debug%get('grid',defaultVal=emptyList)
debugGeneral = debug_grid%contains('basic')
debugRotation = debug_grid%contains('rotation')
debugPETSc = debug_grid%contains('petsc')
@ -218,7 +218,7 @@ subroutine spectral_utilities_init
trim(PETScDebug), &
' add more using the PETSc_Options keyword in numerics.yaml '; flush(6)
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
call PETScOptionsClear(PETSC_NULL_OPTIONS,ierr)
CHKERRQ(ierr)

View File

@ -149,20 +149,20 @@ subroutine homogenization_init
num_homogGeneric, &
debug_homogenization
debug_homogenization => debug_root%get('homogenization', defaultVal=emptyList)
debug_homogenization => config_debug%get('homogenization', defaultVal=emptyList)
debugHomog%basic = debug_homogenization%contains('basic')
debugHomog%extensive = debug_homogenization%contains('extensive')
debugHomog%selective = debug_homogenization%contains('selective')
debugHomog%element = debug_root%get_asInt('element',defaultVal = 1)
debugHomog%ip = debug_root%get_asInt('integrationpoint',defaultVal = 1)
debugHomog%grain = debug_root%get_asInt('grain',defaultVal = 1)
debugHomog%element = config_debug%get_asInt('element',defaultVal = 1)
debugHomog%ip = config_debug%get_asInt('integrationpoint',defaultVal = 1)
debugHomog%grain = config_debug%get_asInt('grain',defaultVal = 1)
if (debugHomog%grain < 1 &
.or. debugHomog%grain > homogenization_Ngrains(material_homogenizationAt(debugHomog%element))) &
call IO_error(602,ext_msg='constituent', el=debugHomog%element, g=debugHomog%grain)
num_homog => numerics_root%get('homogenization',defaultVal=emptyDict)
num_homog => config_numerics%get('homogenization',defaultVal=emptyDict)
num_homogMech => num_homog%get('mech',defaultVal=emptyDict)
num_homogGeneric => num_homog%get('generic',defaultVal=emptyDict)

View File

@ -139,7 +139,7 @@ module subroutine mech_RGC_init(num_homogMech)
if (num%volDiscrPow <= 0.0_pReal) call IO_error(301,ext_msg='volDiscrPw_RGC')
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, size(homogenization_type)
if (homogenization_type(h) /= HOMOGENIZATION_RGC_ID) cycle
homog => material_homogenization%get(h)

View File

@ -10,16 +10,16 @@ submodule(homogenization) homogenization_mech_isostrain
parallel_ID, &
average_ID
end enum
type :: tParameters !< container type for internal constitutive parameters
integer :: &
Nconstituents
integer(kind(average_ID)) :: &
mapping
end type
type(tParameters), dimension(:), allocatable :: param !< containers of constitutive parameters (len Ninstance)
contains
@ -36,21 +36,21 @@ module subroutine mech_isostrain_init
material_homogenization, &
homog, &
homogMech
write(6,'(/,a)') ' <<<+- homogenization_mech_isostrain init -+>>>'
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
allocate(param(Ninstance)) ! one container of parameters per instance
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, size(homogenization_type)
if (homogenization_type(h) /= HOMOGENIZATION_ISOSTRAIN_ID) cycle
homog => material_homogenization%get(h)
homogMech => homog%get('mech')
associate(prm => param(homogenization_typeInstance(h)))
prm%Nconstituents = homogMech%get_asInt('N_constituents')
select case(homogMech%get_asString('mapping',defaultVal = 'sum'))
case ('sum')
@ -60,15 +60,15 @@ module subroutine mech_isostrain_init
case default
call IO_error(211,ext_msg='sum'//' (mech_isostrain)')
end select
NofMyHomog = count(material_homogenizationAt == h)
homogState(h)%sizeState = 0
allocate(homogState(h)%state0 (0,NofMyHomog))
allocate(homogState(h)%subState0(0,NofMyHomog))
allocate(homogState(h)%state (0,NofMyHomog))
end associate
enddo
end subroutine mech_isostrain_init
@ -78,30 +78,30 @@ end subroutine mech_isostrain_init
!> @brief partitions the deformation gradient onto the constituents
!--------------------------------------------------------------------------------------------------
module subroutine mech_isostrain_partitionDeformation(F,avgF)
real(pReal), dimension (:,:,:), intent(out) :: F !< partitioned deformation gradient
real(pReal), dimension (3,3), intent(in) :: avgF !< average deformation gradient at material point
F = spread(avgF,3,size(F,3))
end subroutine mech_isostrain_partitionDeformation
!--------------------------------------------------------------------------------------------------
!> @brief derive average stress and stiffness from constituent quantities
!> @brief derive average stress and stiffness from constituent quantities
!--------------------------------------------------------------------------------------------------
module subroutine mech_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dPdF,instance)
real(pReal), dimension (3,3), intent(out) :: avgP !< average stress at material point
real(pReal), dimension (3,3,3,3), intent(out) :: dAvgPdAvgF !< average stiffness at material point
real(pReal), dimension (:,:,:), intent(in) :: P !< partitioned stresses
real(pReal), dimension (:,:,:,:,:), intent(in) :: dPdF !< partitioned stiffnesses
integer, intent(in) :: instance
integer, intent(in) :: instance
associate(prm => param(instance))
select case (prm%mapping)
case (parallel_ID)
avgP = sum(P,3)
@ -110,7 +110,7 @@ module subroutine mech_isostrain_averageStressAndItsTangent(avgP,dAvgPdAvgF,P,dP
avgP = sum(P,3) /real(prm%Nconstituents,pReal)
dAvgPdAvgF = sum(dPdF,5)/real(prm%Nconstituents,pReal)
end select
end associate
end subroutine mech_isostrain_averageStressAndItsTangent

View File

@ -53,7 +53,7 @@ module function kinematics_cleavage_opening_init(kinematics_length) result(myKin
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(kinematics_cleavage_opening_instance(phases%length), source=0)

View File

@ -56,7 +56,7 @@ module function kinematics_slipplane_opening_init(kinematics_length) result(myKi
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(kinematics_slipplane_opening_instance(phases%length), source=0)
allocate(param(Ninstance))

View File

@ -46,7 +46,7 @@ module function kinematics_thermal_expansion_init(kinematics_length) result(myKi
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(kinematics_thermal_expansion_instance(phases%length), source=0)

View File

@ -459,7 +459,7 @@ subroutine lattice_init
write(6,'(/,a)') ' <<<+- lattice init -+>>>'; flush(6)
phases => material_root%get('phase')
phases => config_material%get('phase')
Nphases = phases%length
allocate(lattice_structure(Nphases),source = lattice_UNDEFINED_ID)

View File

@ -55,7 +55,7 @@ module material
character(len=pStringLen), public, protected, allocatable, dimension(:) :: &
material_name_phase, & !< name of each phase
material_name_homogenization !< name of each homogenization
integer(kind(THERMAL_isothermal_ID)), dimension(:), allocatable, public, protected :: &
thermal_type !< thermal transport model
integer(kind(DAMAGE_none_ID)), dimension(:), allocatable, public, protected :: &
@ -164,24 +164,24 @@ subroutine material_init(restart)
phases, &
material_homogenization
character(len=pStringLen) :: sectionName
write(6,'(/,a)') ' <<<+- material init -+>>>'; flush(6)
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(material_name_phase(phases%length))
do ph = 1, phases%length
write(sectionName,'(i0,a)') ph,'_'
material_name_phase(ph) = trim(adjustl(sectionName))//phases%getKey(ph) !ToDO: No reason to do. Update damage tests
material_name_phase(ph) = trim(adjustl(sectionName))//phases%getKey(ph) !ToDO: No reason to do. Update damage tests
enddo
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
allocate(material_name_homogenization(material_homogenization%length))
do myHomog = 1, material_homogenization%length
write(sectionName,'(i0,a)') myHomog,'_'
write(sectionName,'(i0,a)') myHomog,'_'
material_name_homogenization(myHomog) = trim(adjustl(sectionName))//material_homogenization%getKey(myHomog)
enddo
debug_material => debug_root%get('material',defaultVal=emptyList)
debug_material => config_debug%get('material',defaultVal=emptyList)
call material_parseMicrostructure()
if (debug_material%contains('basic')) write(6,'(a)') ' Microstructure parsed'; flush(6)
@ -242,7 +242,7 @@ subroutine material_parseHomogenization
integer :: h
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
material_Nhomogenization = material_homogenization%length
allocate(homogenization_type(material_Nhomogenization), source=HOMOGENIZATION_undefined_ID)
@ -325,18 +325,18 @@ subroutine material_parseMicrostructure
class(tNode), pointer :: microstructure, & !> pointer to microstructure list
constituentsInMicrostructure, & !> pointer to a microstructure list item
constituents, & !> pointer to constituents list
constituent, & !> pointer to each constituent
constituents, & !> pointer to constituents list
constituent, & !> pointer to each constituent
phases, &
homogenization
integer, dimension(:), allocatable :: &
CounterPhase, &
CounterHomogenization
real(pReal), dimension(:,:), allocatable :: &
microstructure_fraction !< vol fraction of each constituent in microstrcuture
microstructure_fraction !< vol fraction of each constituent in microstrcuture
integer :: &
e, &
@ -347,11 +347,11 @@ subroutine material_parseMicrostructure
real(pReal), dimension(4) :: phase_orientation
homogenization => material_root%get('homogenization')
phases => material_root%get('phase')
microstructure => material_root%get('microstructure')
homogenization => config_material%get('homogenization')
phases => config_material%get('phase')
microstructure => config_material%get('microstructure')
allocate(microstructure_Nconstituents(microstructure%length), source = 0)
if(any(discretization_microstructureAt > microstructure%length)) &
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.yaml')
@ -360,7 +360,7 @@ subroutine material_parseMicrostructure
constituents => constituentsInMicrostructure%get('constituents')
microstructure_Nconstituents(m) = constituents%length
enddo
microstructure_maxNconstituents = maxval(microstructure_Nconstituents)
allocate(microstructure_fraction(microstructure_maxNconstituents,microstructure%length), source =0.0_pReal)
allocate(material_phaseAt(microstructure_maxNconstituents,discretization_nElem), source =0)
@ -379,7 +379,7 @@ subroutine material_parseMicrostructure
constituent => constituents%get(c)
microstructure_fraction(c,m) = constituent%get_asFloat('fraction')
enddo
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) call IO_error(153,ext_msg='constituent')
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) call IO_error(153,ext_msg='constituent')
enddo
do e = 1, discretization_nElem
@ -394,11 +394,11 @@ subroutine material_parseMicrostructure
enddo
enddo
enddo
do e = 1, discretization_nElem
do i = 1, discretization_nIP
constituentsInMicrostructure => microstructure%get(discretization_microstructureAt(e))
material_homogenizationAt(e) = homogenization%getIndex(constituentsInMicrostructure%get_asString('homogenization'))
constituentsInMicrostructure => microstructure%get(discretization_microstructureAt(e))
material_homogenizationAt(e) = homogenization%getIndex(constituentsInMicrostructure%get_asString('homogenization'))
CounterHomogenization(material_homogenizationAt(e)) = CounterHomogenization(material_homogenizationAt(e)) + 1
material_homogenizationMemberAt(i,e) = CounterHomogenization(material_homogenizationAt(e))
enddo
@ -419,5 +419,5 @@ subroutine material_parseMicrostructure
end subroutine material_parseMicrostructure
end module material

View File

@ -97,7 +97,7 @@ subroutine math_init
write(6,'(/,a)') ' <<<+- math init -+>>>'; flush(6)
num_generic => numerics_root%get('generic',defaultVal=emptyDict)
num_generic => config_numerics%get('generic',defaultVal=emptyDict)
randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0)
call random_seed(size=randSize)

View File

@ -57,7 +57,7 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_damage_anisoBrittle_offset (phases%length), source=0)
allocate(source_damage_anisoBrittle_instance(phases%length), source=0)

View File

@ -52,7 +52,7 @@ module function source_damage_anisoDuctile_init(source_length) result(mySources)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_damage_anisoDuctile_offset (phases%length), source=0)
allocate(source_damage_anisoDuctile_instance(phases%length), source=0)

View File

@ -47,7 +47,7 @@ module function source_damage_isoBrittle_init(source_length) result(mySources)
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_damage_isoBrittle_offset (phases%length), source=0)
allocate(source_damage_isoBrittle_instance(phases%length), source=0)

View File

@ -49,7 +49,7 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_damage_isoDuctile_offset (phases%length), source=0)
allocate(source_damage_isoDuctile_instance(phases%length), source=0)

View File

@ -45,7 +45,7 @@ module function source_thermal_dissipation_init(source_length) result(mySources)
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_thermal_dissipation_offset (phases%length), source=0)
allocate(source_thermal_dissipation_instance(phases%length), source=0)

View File

@ -49,7 +49,7 @@ module function source_thermal_externalheat_init(source_length) result(mySources
write(6,'(a16,1x,i5,/)') '# instances:',Ninstance; flush(6)
if(Ninstance == 0) return
phases => material_root%get('phase')
phases => config_material%get('phase')
allocate(param(Ninstance))
allocate(source_thermal_externalheat_offset (phases%length), source=0)
allocate(source_thermal_externalheat_instance(phases%length), source=0)

View File

@ -53,7 +53,7 @@ subroutine thermal_adiabatic_init
allocate(param(maxNinstance))
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, material_Nhomogenization
if (thermal_type(h) /= THERMAL_adiabatic_ID) cycle
homog => material_homogenization%get(h)

View File

@ -52,7 +52,7 @@ subroutine thermal_conduction_init
Ninstance = count(thermal_type == THERMAL_conduction_ID)
allocate(param(Ninstance))
material_homogenization => material_root%get('homogenization')
material_homogenization => config_material%get('homogenization')
do h = 1, material_Nhomogenization
if (thermal_type(h) /= THERMAL_conduction_ID) cycle
homog => material_homogenization%get(h)