Merge branch 'Fortran-simplifications' into 'development'

Fortran simplifications

See merge request damask/DAMASK!230
This commit is contained in:
Martin Diehl 2020-09-23 10:52:15 +02:00
commit 14bfaa60c0
52 changed files with 344 additions and 380 deletions

View File

@ -106,7 +106,7 @@ subroutine CPFEM_init
num_commercialFEM, & num_commercialFEM, &
debug_CPFEM debug_CPFEM
print'(/,a)', ' <<<+- CPFEM init -+>>>'; flush(6) print'(/,a)', ' <<<+- CPFEM init -+>>>'; flush(IO_STDOUT)
allocate(CPFEM_cs( 6,discretization_nIP,discretization_nElem), source= 0.0_pReal) allocate(CPFEM_cs( 6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
allocate(CPFEM_dcsdE( 6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal) allocate(CPFEM_dcsdE( 6,6,discretization_nIP,discretization_nElem), source= 0.0_pReal)
@ -132,7 +132,7 @@ subroutine CPFEM_init
print'(a32,1x,6(i8,1x))', 'CPFEM_cs: ', shape(CPFEM_cs) print'(a32,1x,6(i8,1x))', 'CPFEM_cs: ', shape(CPFEM_cs)
print'(a32,1x,6(i8,1x))', 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE) print'(a32,1x,6(i8,1x))', 'CPFEM_dcsdE: ', shape(CPFEM_dcsdE)
print'(a32,1x,6(i8,1x),/)', 'CPFEM_dcsdE_knownGood: ', shape(CPFEM_dcsdE_knownGood) print'(a32,1x,6(i8,1x),/)', 'CPFEM_dcsdE_knownGood: ', shape(CPFEM_dcsdE_knownGood)
flush(6) flush(IO_STDOUT)
endif endif
end subroutine CPFEM_init end subroutine CPFEM_init
@ -250,7 +250,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, temperature_inp, dt, elFE, ip, cauchyS
'<< CPFEM >> stress/MPa at elFE ip ', elFE, ip, CPFEM_cs(1:6,ip,elCP)*1.0e-6_pReal '<< CPFEM >> stress/MPa at elFE ip ', elFE, ip, CPFEM_cs(1:6,ip,elCP)*1.0e-6_pReal
print'(a,i8,1x,i2,/,6(12x,6(f10.3,1x)/))', & print'(a,i8,1x,i2,/,6(12x,6(f10.3,1x)/))', &
'<< CPFEM >> Jacobian/GPa at elFE ip ', elFE, ip, transpose(CPFEM_dcsdE(1:6,1:6,ip,elCP))*1.0e-9_pReal '<< CPFEM >> Jacobian/GPa at elFE ip ', elFE, ip, transpose(CPFEM_dcsdE(1:6,1:6,ip,elCP))*1.0e-9_pReal
flush(6) flush(IO_STDOUT)
endif endif
endif endif

View File

@ -76,7 +76,7 @@ end subroutine CPFEM_initAll
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine CPFEM_init subroutine CPFEM_init
print'(/,a)', ' <<<+- CPFEM init -+>>>'; flush(6) print'(/,a)', ' <<<+- CPFEM init -+>>>'; flush(IO_STDOUT)
if (interface_restartInc > 0) call crystallite_restartRead if (interface_restartInc > 0) call crystallite_restartRead

View File

@ -14,7 +14,7 @@
#define PETSC_MINOR_MAX 13 #define PETSC_MINOR_MAX 13
module DAMASK_interface module DAMASK_interface
use, intrinsic :: iso_fortran_env use, intrinsic :: ISO_fortran_env
use PETScSys use PETScSys
@ -82,7 +82,7 @@ subroutine DAMASK_interface_init
print'(/,a)', ' <<<+- DAMASK_interface init -+>>>' print'(/,a)', ' <<<+- DAMASK_interface init -+>>>'
open(6, encoding='UTF-8') ! for special characters in output open(OUTPUT_unit, encoding='UTF-8') ! for special characters in output
! http://patorjk.com/software/taag/#p=display&f=Lean&t=DAMASK%203 ! http://patorjk.com/software/taag/#p=display&f=Lean&t=DAMASK%203
#ifdef DEBUG #ifdef DEBUG
@ -101,8 +101,8 @@ subroutine DAMASK_interface_init
#endif #endif
print*, achar(27)//'[0m' print*, achar(27)//'[0m'
print'(a)', ' Roters et al., Computational Materials Science 158:420478, 2019' print*, 'Roters et al., Computational Materials Science 158:420478, 2019'
print'(a)', ' https://doi.org/10.1016/j.commatsci.2018.04.030' print*, 'https://doi.org/10.1016/j.commatsci.2018.04.030'
print'(/,a)', ' Version: '//DAMASKVERSION print'(/,a)', ' Version: '//DAMASKVERSION
@ -373,7 +373,7 @@ function makeRelativePath(a,b)
a_cleaned = rectifyPath(trim(a)//'/') a_cleaned = rectifyPath(trim(a)//'/')
b_cleaned = rectifyPath(b) b_cleaned = rectifyPath(b)
do i = 1, min(1024,len_trim(a_cleaned),len_trim(rectifyPath(b_cleaned))) do i = 1, min(len_trim(a_cleaned),len_trim(rectifyPath(b_cleaned)))
if (a_cleaned(i:i) /= b_cleaned(i:i)) exit if (a_cleaned(i:i) /= b_cleaned(i:i)) exit
if (a_cleaned(i:i) == '/') posLastCommonSlash = i if (a_cleaned(i:i) == '/') posLastCommonSlash = i
enddo enddo
@ -395,7 +395,7 @@ subroutine catchSIGTERM(signal) bind(C)
integer(C_INT), value :: signal integer(C_INT), value :: signal
interface_SIGTERM = .true. interface_SIGTERM = .true.
print'(a,i2.2,a)', ' received signal ',signal, ', set SIGTERM=TRUE' print'(a,i0,a)', ' received signal ',signal, ', set SIGTERM=TRUE'
end subroutine catchSIGTERM end subroutine catchSIGTERM
@ -420,7 +420,7 @@ subroutine catchSIGUSR1(signal) bind(C)
integer(C_INT), value :: signal integer(C_INT), value :: signal
interface_SIGUSR1 = .true. interface_SIGUSR1 = .true.
print'(a,i2.2,a)', ' received signal ',signal, ', set SIGUSR1=TRUE' print'(a,i0,a)', ' received signal ',signal, ', set SIGUSR1=TRUE'
end subroutine catchSIGUSR1 end subroutine catchSIGUSR1
@ -445,7 +445,7 @@ subroutine catchSIGUSR2(signal) bind(C)
integer(C_INT), value :: signal integer(C_INT), value :: signal
interface_SIGUSR2 = .true. interface_SIGUSR2 = .true.
print'(a,i2.2,a)', ' received signal ',signal, ', set SIGUSR2=TRUE' print'(a,i0,a)', ' received signal ',signal, ', set SIGUSR2=TRUE'
end subroutine catchSIGUSR2 end subroutine catchSIGUSR2

View File

@ -30,7 +30,7 @@
module DAMASK_interface module DAMASK_interface
use prec use prec
#if __INTEL_COMPILER >= 1800 #if __INTEL_COMPILER >= 1800
use, intrinsic :: iso_fortran_env, only: & use, intrinsic :: ISO_fortran_env, only: &
compiler_version, & compiler_version, &
compiler_options compiler_options
#endif #endif

View File

@ -6,6 +6,10 @@
!> @brief input/output functions !> @brief input/output functions
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module IO module IO
use, intrinsic :: ISO_fortran_env, only: &
IO_STDOUT => OUTPUT_UNIT, &
IO_STDERR => ERROR_UNIT
use prec use prec
implicit none implicit none
@ -16,7 +20,7 @@ module IO
character, parameter, public :: & character, parameter, public :: &
IO_EOL = new_line('DAMASK'), & !< end of line character IO_EOL = new_line('DAMASK'), & !< end of line character
IO_COMMENT = '#' IO_COMMENT = '#'
character(len=*), parameter, private :: & character(len=*), parameter :: &
IO_DIVIDER = '───────────────────'//& IO_DIVIDER = '───────────────────'//&
'───────────────────'//& '───────────────────'//&
'───────────────────'//& '───────────────────'//&
@ -37,7 +41,8 @@ module IO
IO_stringAsFloat, & IO_stringAsFloat, &
IO_stringAsBool, & IO_stringAsBool, &
IO_error, & IO_error, &
IO_warning IO_warning, &
IO_STDOUT
contains contains
@ -47,7 +52,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine IO_init subroutine IO_init
print'(/,a)', ' <<<+- IO init -+>>>'; flush(6) print'(/,a)', ' <<<+- IO init -+>>>'; flush(IO_STDOUT)
call selfTest call selfTest
@ -538,29 +543,29 @@ subroutine IO_error(error_ID,el,ip,g,instance,ext_msg)
end select end select
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
write(0,'(/,a)') ' ┌'//IO_DIVIDER//'┐' write(IO_STDERR,'(/,a)') ' ┌'//IO_DIVIDER//'┐'
write(0,'(a,24x,a,40x,a)') ' │','error', '│' write(IO_STDERR,'(a,24x,a,40x,a)') ' │','error', '│'
write(0,'(a,24x,i3,42x,a)') ' │',error_ID, '│' write(IO_STDERR,'(a,24x,i3,42x,a)') ' │',error_ID, '│'
write(0,'(a)') ' ├'//IO_DIVIDER//'┤' write(IO_STDERR,'(a)') ' ├'//IO_DIVIDER//'┤'
write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(msg)),',',& write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(msg)),',',&
max(1,72-len_trim(msg)-4),'x,a)' max(1,72-len_trim(msg)-4),'x,a)'
write(0,formatString) '│ ',trim(msg), '│' write(IO_STDERR,formatString) '│ ',trim(msg), '│'
if (present(ext_msg)) then if (present(ext_msg)) then
write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(ext_msg)),',',& write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(ext_msg)),',',&
max(1,72-len_trim(ext_msg)-4),'x,a)' max(1,72-len_trim(ext_msg)-4),'x,a)'
write(0,formatString) '│ ',trim(ext_msg), '│' write(IO_STDERR,formatString) '│ ',trim(ext_msg), '│'
endif endif
if (present(el)) & if (present(el)) &
write(0,'(a19,1x,i9,44x,a3)') ' │ at element ',el, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at element ',el, '│'
if (present(ip)) & if (present(ip)) &
write(0,'(a19,1x,i9,44x,a3)') ' │ at IP ',ip, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at IP ',ip, '│'
if (present(g)) & if (present(g)) &
write(0,'(a19,1x,i9,44x,a3)') ' │ at constituent',g, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at constituent',g, '│'
if (present(instance)) & if (present(instance)) &
write(0,'(a19,1x,i9,44x,a3)') ' │ at instance ',instance, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at instance ',instance, '│'
write(0,'(a,69x,a)') ' │', '│' write(IO_STDERR,'(a,69x,a)') ' │', '│'
write(0,'(a)') ' └'//IO_DIVIDER//'┘' write(IO_STDERR,'(a)') ' └'//IO_DIVIDER//'┘'
flush(0) flush(IO_STDERR)
call quit(9000+error_ID) call quit(9000+error_ID)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
@ -623,27 +628,27 @@ subroutine IO_warning(warning_ID,el,ip,g,ext_msg)
end select end select
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
write(6,'(/,a)') ' ┌'//IO_DIVIDER//'┐' write(IO_STDERR,'(/,a)') ' ┌'//IO_DIVIDER//'┐'
write(6,'(a,24x,a,38x,a)') ' │','warning', '│' write(IO_STDERR,'(a,24x,a,38x,a)') ' │','warning', '│'
write(6,'(a,24x,i3,42x,a)') ' │',warning_ID, '│' write(IO_STDERR,'(a,24x,i3,42x,a)') ' │',warning_ID, '│'
write(6,'(a)') ' ├'//IO_DIVIDER//'┤' write(IO_STDERR,'(a)') ' ├'//IO_DIVIDER//'┤'
write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(msg)),',',& write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(msg)),',',&
max(1,72-len_trim(msg)-4),'x,a)' max(1,72-len_trim(msg)-4),'x,a)'
write(6,formatString) '│ ',trim(msg), '│' write(IO_STDERR,formatString) '│ ',trim(msg), '│'
if (present(ext_msg)) then if (present(ext_msg)) then
write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(ext_msg)),',',& write(formatString,'(a,i6.6,a,i6.6,a)') '(1x,a4,a',max(1,len_trim(ext_msg)),',',&
max(1,72-len_trim(ext_msg)-4),'x,a)' max(1,72-len_trim(ext_msg)-4),'x,a)'
write(6,formatString) '│ ',trim(ext_msg), '│' write(IO_STDERR,formatString) '│ ',trim(ext_msg), '│'
endif endif
if (present(el)) & if (present(el)) &
write(6,'(a19,1x,i9,44x,a3)') ' │ at element ',el, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at element ',el, '│'
if (present(ip)) & if (present(ip)) &
write(6,'(a19,1x,i9,44x,a3)') ' │ at IP ',ip, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at IP ',ip, '│'
if (present(g)) & if (present(g)) &
write(6,'(a19,1x,i9,44x,a3)') ' │ at constituent',g, '│' write(IO_STDERR,'(a19,1x,i9,44x,a3)') ' │ at constituent',g, '│'
write(6,'(a,69x,a)') ' │', '│' write(IO_STDERR,'(a,69x,a)') ' │', '│'
write(6,'(a)') ' └'//IO_DIVIDER//'┘' write(IO_STDERR,'(a)') ' └'//IO_DIVIDER//'┘'
flush(6) flush(IO_STDERR)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
end subroutine IO_warning end subroutine IO_warning

View File

@ -27,7 +27,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine base64_init subroutine base64_init
print'(/,a)', ' <<<+- base64 init -+>>>'; flush(6) print'(/,a)', ' <<<+- base64 init -+>>>'; flush(IO_STDOUT)
call selfTest call selfTest

View File

@ -35,7 +35,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine config_init subroutine config_init
print'(/,a)', ' <<<+- config init -+>>>'; flush(6) print'(/,a)', ' <<<+- config init -+>>>'; flush(IO_STDOUT)
call parse_material call parse_material
call parse_numerics call parse_numerics
@ -59,7 +59,7 @@ subroutine parse_material
inquire(file=fname,exist=fileExists) inquire(file=fname,exist=fileExists)
if(.not. fileExists) call IO_error(100,ext_msg=fname) if(.not. fileExists) call IO_error(100,ext_msg=fname)
endif endif
print*, 'reading '//fname; flush(6) print*, 'reading '//fname; flush(IO_STDOUT)
config_material => YAML_parse_file(fname) config_material => YAML_parse_file(fname)
end subroutine parse_material end subroutine parse_material
@ -75,7 +75,7 @@ subroutine parse_numerics
config_numerics => emptyDict config_numerics => emptyDict
inquire(file='numerics.yaml', exist=fexist) inquire(file='numerics.yaml', exist=fexist)
if (fexist) then if (fexist) then
print*, 'reading numerics.yaml'; flush(6) print*, 'reading numerics.yaml'; flush(IO_STDOUT)
config_numerics => YAML_parse_file('numerics.yaml') config_numerics => YAML_parse_file('numerics.yaml')
endif endif
@ -92,7 +92,7 @@ subroutine parse_debug
config_debug => emptyDict config_debug => emptyDict
inquire(file='debug.yaml', exist=fexist) inquire(file='debug.yaml', exist=fexist)
fileExists: if (fexist) then fileExists: if (fexist) then
print*, 'reading debug.yaml'; flush(6) print*, 'reading debug.yaml'; flush(IO_STDOUT)
config_debug => YAML_parse_file('debug.yaml') config_debug => YAML_parse_file('debug.yaml')
endif fileExists endif fileExists

View File

@ -446,7 +446,7 @@ subroutine constitutive_init
call damage_init call damage_init
call thermal_init call thermal_init
print'(/,a)', ' <<<+- constitutive init -+>>>'; flush(6) print'(/,a)', ' <<<+- constitutive init -+>>>'; flush(IO_STDOUT)
constitutive_source_maxSizeDotState = 0 constitutive_source_maxSizeDotState = 0
PhaseLoop2:do p = 1,phases%length PhaseLoop2:do p = 1,phases%length

View File

@ -100,7 +100,7 @@ module function plastic_disloTungsten_init() result(myPlasticity)
myPlasticity = plastic_active('disloTungsten') myPlasticity = plastic_active('disloTungsten')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
print*, 'Cereceda et al., International Journal of Plasticity 78:242256, 2016' print*, 'Cereceda et al., International Journal of Plasticity 78:242256, 2016'

View File

@ -147,7 +147,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
myPlasticity = plastic_active('dislotwin') myPlasticity = plastic_active('dislotwin')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
print*, 'Ma and Roters, Acta Materialia 52(12):36033612, 2004' print*, 'Ma and Roters, Acta Materialia 52(12):36033612, 2004'

View File

@ -71,7 +71,7 @@ module function plastic_isotropic_init() result(myPlasticity)
myPlasticity = plastic_active('isotropic') myPlasticity = plastic_active('isotropic')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
print*, 'Maiti and Eisenlohr, Scripta Materialia 145:3740, 2018' print*, 'Maiti and Eisenlohr, Scripta Materialia 145:3740, 2018'

View File

@ -83,7 +83,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
myPlasticity = plastic_active('kinehardening') myPlasticity = plastic_active('kinehardening')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
allocate(param(Ninstance)) allocate(param(Ninstance))

View File

@ -35,7 +35,7 @@ module function plastic_none_init() result(myPlasticity)
enddo enddo
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
do p = 1, phases%length do p = 1, phases%length

View File

@ -189,7 +189,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
myPlasticity = plastic_active('nonlocal') myPlasticity = plastic_active('nonlocal')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) then if(Ninstance == 0) then
call geometry_plastic_nonlocal_disable call geometry_plastic_nonlocal_disable
return return
@ -199,7 +199,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
print*, 'https://doi.org/10.1016/j.actamat.2014.03.012'//IO_EOL print*, 'https://doi.org/10.1016/j.actamat.2014.03.012'//IO_EOL
print*, 'Kords, Dissertation RWTH Aachen, 2014' print*, 'Kords, Dissertation RWTH Aachen, 2014'
print*, 'http://publications.rwth-aachen.de/record/229993'//IO_EOL print*, 'http://publications.rwth-aachen.de/record/229993'
allocate(param(Ninstance)) allocate(param(Ninstance))
allocate(state(Ninstance)) allocate(state(Ninstance))
@ -741,10 +741,10 @@ module subroutine plastic_nonlocal_dependentState(F, Fp, instance, of, ip, el)
if (debugConstitutive%extensive & if (debugConstitutive%extensive &
.and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip)& .and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip)&
.or. .not. debugConstitutive%selective)) then .or. .not. debugConstitutive%selective)) then
write(6,'(/,a,i8,1x,i2,1x,i1,/)') '<< CONST >> nonlocal_microstructure at el ip ',el,ip print'(/,a,i8,1x,i2,1x,i1,/)', '<< CONST >> nonlocal_microstructure at el ip ',el,ip
write(6,'(a,/,12x,12(e10.3,1x))') '<< CONST >> rhoForest', stt%rho_forest(:,of) print'(a,/,12x,12(e10.3,1x))', '<< CONST >> rhoForest', stt%rho_forest(:,of)
write(6,'(a,/,12x,12(f10.5,1x))') '<< CONST >> tauThreshold / MPa', dst%tau_pass(:,of)*1e-6 print'(a,/,12x,12(f10.5,1x))', '<< CONST >> tauThreshold / MPa', dst%tau_pass(:,of)*1e-6
write(6,'(a,/,12x,12(f10.5,1x),/)') '<< CONST >> tauBack / MPa', dst%tau_back(:,of)*1e-6 print'(a,/,12x,12(f10.5,1x),/)', '<< CONST >> tauBack / MPa', dst%tau_back(:,of)*1e-6
endif endif
#endif #endif
@ -958,8 +958,8 @@ module subroutine plastic_nonlocal_deltaState(Mp,instance,of,ip,el)
if (debugConstitutive%extensive & if (debugConstitutive%extensive &
.and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip)& .and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip)&
.or. .not. debugConstitutive%selective)) then .or. .not. debugConstitutive%selective)) then
write(6,'(a,/,8(12x,12(e12.5,1x),/))') '<< CONST >> dislocation remobilization', deltaRhoRemobilization(:,1:8) print'(a,/,8(12x,12(e12.5,1x),/))', '<< CONST >> dislocation remobilization', deltaRhoRemobilization(:,1:8)
write(6,'(a,/,10(12x,12(e12.5,1x),/),/)') '<< CONST >> dipole dissociation by stress increase', deltaRhoDipole2SingleStress print'(a,/,10(12x,12(e12.5,1x),/),/)', '<< CONST >> dipole dissociation by stress increase', deltaRhoDipole2SingleStress
endif endif
#endif #endif
@ -1047,8 +1047,8 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
if (debugConstitutive%basic & if (debugConstitutive%basic &
.and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip) & .and. ((debugConstitutive%element == el .and. debugConstitutive%ip == ip) &
.or. .not. debugConstitutive%selective)) then .or. .not. debugConstitutive%selective)) then
write(6,'(a,/,10(12x,12(e12.5,1x),/))') '<< CONST >> rho / 1/m^2', rhoSgl, rhoDip print'(a,/,10(12x,12(e12.5,1x),/))', '<< CONST >> rho / 1/m^2', rhoSgl, rhoDip
write(6,'(a,/,4(12x,12(e12.5,1x),/))') '<< CONST >> gdot / 1/s',gdot print'(a,/,4(12x,12(e12.5,1x),/))', '<< CONST >> gdot / 1/s',gdot
endif endif
#endif #endif
@ -1156,8 +1156,8 @@ module subroutine plastic_nonlocal_dotState(Mp, F, Fp, Temperature,timestep, &
.or. any(rho(:,dip) + rhoDot(:,9:10) * timestep < -prm%atol_rho)) then .or. any(rho(:,dip) + rhoDot(:,9:10) * timestep < -prm%atol_rho)) then
#ifdef DEBUG #ifdef DEBUG
if (debugConstitutive%extensive) then if (debugConstitutive%extensive) then
write(6,'(a,i5,a,i2)') '<< CONST >> evolution rate leads to negative density at el ',el,' ip ',ip print'(a,i5,a,i2)', '<< CONST >> evolution rate leads to negative density at el ',el,' ip ',ip
write(6,'(a)') '<< CONST >> enforcing cutback !!!' print'(a)', '<< CONST >> enforcing cutback !!!'
endif endif
#endif #endif
plasticState(ph)%dotState = IEEE_value(1.0_pReal,IEEE_quiet_NaN) plasticState(ph)%dotState = IEEE_value(1.0_pReal,IEEE_quiet_NaN)
@ -1268,8 +1268,8 @@ function rhoDotFlux(F,Fp,timestep, instance,of,ip,el)
> IPvolume(ip,el) / maxval(IParea(:,ip,el)))) then ! ...with velocity above critical value (we use the reference volume and area for simplicity here) > IPvolume(ip,el) / maxval(IParea(:,ip,el)))) then ! ...with velocity above critical value (we use the reference volume and area for simplicity here)
#ifdef DEBUG #ifdef DEBUG
if (debugConstitutive%extensive) then if (debugConstitutive%extensive) then
write(6,'(a,i5,a,i2)') '<< CONST >> CFL condition not fullfilled at el ',el,' ip ',ip print'(a,i5,a,i2)', '<< CONST >> CFL condition not fullfilled at el ',el,' ip ',ip
write(6,'(a,e10.3,a,e10.3)') '<< CONST >> velocity is at ', & print'(a,e10.3,a,e10.3)', '<< CONST >> velocity is at ', &
maxval(abs(v0), abs(gdot) > 0.0_pReal & maxval(abs(v0), abs(gdot) > 0.0_pReal &
.and. prm%CFLfactor * abs(v0) * timestep & .and. prm%CFLfactor * abs(v0) * timestep &
> IPvolume(ip,el) / maxval(IParea(:,ip,el))), & > IPvolume(ip,el) / maxval(IParea(:,ip,el))), &

View File

@ -92,7 +92,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
myPlasticity = plastic_active('phenopowerlaw') myPlasticity = plastic_active('phenopowerlaw')
Ninstance = count(myPlasticity) Ninstance = count(myPlasticity)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
allocate(param(Ninstance)) allocate(param(Ninstance))

View File

@ -294,7 +294,7 @@ subroutine crystallite_init
print'(a42,1x,i10)', ' # of elements: ', eMax print'(a42,1x,i10)', ' # of elements: ', eMax
print'(a42,1x,i10)', ' # of integration points/element: ', iMax print'(a42,1x,i10)', ' # of integration points/element: ', iMax
print'(a42,1x,i10)', 'max # of constituents/integration point: ', cMax print'(a42,1x,i10)', 'max # of constituents/integration point: ', cMax
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -1561,7 +1561,7 @@ subroutine crystallite_restartWrite
integer(HID_T) :: fileHandle, groupHandle integer(HID_T) :: fileHandle, groupHandle
character(len=pStringLen) :: fileName, datasetName character(len=pStringLen) :: fileName, datasetName
print*, ' writing field and constitutive data required for restart to file';flush(6) print*, ' writing field and constitutive data required for restart to file';flush(IO_STDOUT)
write(fileName,'(a,i0,a)') trim(getSolverJobName())//'_',worldrank,'.hdf5' write(fileName,'(a,i0,a)') trim(getSolverJobName())//'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName,'a') fileHandle = HDF5_openFile(fileName,'a')

View File

@ -49,7 +49,7 @@ subroutine damage_local_init
homog, & homog, &
homogDamage homogDamage
print'(/,a)', ' <<<+- damage_local init -+>>>'; flush(6) print'(/,a)', ' <<<+- damage_local init -+>>>'; flush(IO_STDOUT)
!---------------------------------------------------------------------------------------------- !----------------------------------------------------------------------------------------------
! read numerics parameter and do sanity check ! read numerics parameter and do sanity check

View File

@ -922,7 +922,7 @@ subroutine tElement_init(self,elemType)
self%nIPneighbors = size(self%IPneighbor,1) self%nIPneighbors = size(self%IPneighbor,1)
print'(/,a)', ' <<<+- element_init -+>>>'; flush(6) print'(/,a)', ' <<<+- element_init -+>>>'; flush(IO_STDOUT)
print*, 'element type: ',self%elemType print*, 'element type: ',self%elemType
print*, ' geom type: ',self%geomType print*, ' geom type: ',self%geomType

View File

@ -99,10 +99,10 @@ program DAMASK_grid
! init DAMASK (all modules) ! init DAMASK (all modules)
call CPFEM_initAll call CPFEM_initAll
write(6,'(/,a)') ' <<<+- DAMASK_spectral init -+>>>'; flush(6) print'(/,a)', ' <<<+- DAMASK_spectral init -+>>>'; flush(IO_STDOUT)
write(6,'(/,a)') ' Shanthraj et al., Handbook of Mechanics of Materials, 2019' print*, 'Shanthraj et al., Handbook of Mechanics of Materials, 2019'
write(6,'(a)') ' https://doi.org/10.1007/978-981-10-6855-3_80' print*, 'https://doi.org/10.1007/978-981-10-6855-3_80'
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! initialize field solver information ! initialize field solver information
@ -263,56 +263,56 @@ program DAMASK_grid
reportAndCheck: if (worldrank == 0) then reportAndCheck: if (worldrank == 0) then
write (loadcase_string, '(i0)' ) currentLoadCase write (loadcase_string, '(i0)' ) currentLoadCase
write(6,'(/,1x,a,i0)') 'load case: ', currentLoadCase print'(/,a,i0)', ' load case: ', currentLoadCase
if (.not. newLoadCase%followFormerTrajectory) & if (.not. newLoadCase%followFormerTrajectory) &
write(6,'(2x,a)') 'drop guessing along trajectory' print*, ' drop guessing along trajectory'
if (newLoadCase%deformation%myType == 'l') then if (newLoadCase%deformation%myType == 'l') then
do j = 1, 3 do j = 1, 3
if (any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .true.) .and. & if (any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .true.) .and. &
any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .false.)) errorID = 832 ! each row should be either fully or not at all defined any(newLoadCase%deformation%maskLogical(j,1:3) .eqv. .false.)) errorID = 832 ! each row should be either fully or not at all defined
enddo enddo
write(6,'(2x,a)') 'velocity gradient:' print*, ' velocity gradient:'
else if (newLoadCase%deformation%myType == 'f') then else if (newLoadCase%deformation%myType == 'f') then
write(6,'(2x,a)') 'deformation gradient at end of load case:' print*, ' deformation gradient at end of load case:'
else else
write(6,'(2x,a)') 'deformation gradient rate:' print*, ' deformation gradient rate:'
endif endif
do i = 1, 3; do j = 1, 3 do i = 1, 3; do j = 1, 3
if(newLoadCase%deformation%maskLogical(i,j)) then if(newLoadCase%deformation%maskLogical(i,j)) then
write(6,'(2x,f12.7)',advance='no') newLoadCase%deformation%values(i,j) write(IO_STDOUT,'(2x,f12.7)',advance='no') newLoadCase%deformation%values(i,j)
else else
write(6,'(2x,12a)',advance='no') ' * ' write(IO_STDOUT,'(2x,12a)',advance='no') ' * '
endif endif
enddo; write(6,'(/)',advance='no') enddo; write(IO_STDOUT,'(/)',advance='no')
enddo enddo
if (any(newLoadCase%stress%maskLogical .eqv. & if (any(newLoadCase%stress%maskLogical .eqv. &
newLoadCase%deformation%maskLogical)) errorID = 831 ! exclusive or masking only newLoadCase%deformation%maskLogical)) errorID = 831 ! exclusive or masking only
if (any(newLoadCase%stress%maskLogical .and. transpose(newLoadCase%stress%maskLogical) & if (any(newLoadCase%stress%maskLogical .and. transpose(newLoadCase%stress%maskLogical) &
.and. (math_I3<1))) errorID = 838 ! no rotation is allowed by stress BC .and. (math_I3<1))) errorID = 838 ! no rotation is allowed by stress BC
write(6,'(2x,a)') 'stress / GPa:' print*, ' stress / GPa:'
do i = 1, 3; do j = 1, 3 do i = 1, 3; do j = 1, 3
if(newLoadCase%stress%maskLogical(i,j)) then if(newLoadCase%stress%maskLogical(i,j)) then
write(6,'(2x,f12.7)',advance='no') newLoadCase%stress%values(i,j)*1e-9_pReal write(IO_STDOUT,'(2x,f12.7)',advance='no') newLoadCase%stress%values(i,j)*1e-9_pReal
else else
write(6,'(2x,12a)',advance='no') ' * ' write(IO_STDOUT,'(2x,12a)',advance='no') ' * '
endif endif
enddo; write(6,'(/)',advance='no') enddo; write(IO_STDOUT,'(/)',advance='no')
enddo enddo
if (any(abs(matmul(newLoadCase%rot%asMatrix(), & if (any(abs(matmul(newLoadCase%rot%asMatrix(), &
transpose(newLoadCase%rot%asMatrix()))-math_I3) > & transpose(newLoadCase%rot%asMatrix()))-math_I3) > &
reshape(spread(tol_math_check,1,9),[ 3,3]))) errorID = 846 ! given rotation matrix contains strain reshape(spread(tol_math_check,1,9),[ 3,3]))) errorID = 846 ! given rotation matrix contains strain
if (any(dNeq(newLoadCase%rot%asMatrix(), math_I3))) & if (any(dNeq(newLoadCase%rot%asMatrix(), math_I3))) &
write(6,'(2x,a,/,3(3(3x,f12.7,1x)/))',advance='no') 'rotation of loadframe:',& write(IO_STDOUT,'(2x,a,/,3(3(3x,f12.7,1x)/))',advance='no') 'rotation of loadframe:',&
transpose(newLoadCase%rot%asMatrix()) transpose(newLoadCase%rot%asMatrix())
if (newLoadCase%time < 0.0_pReal) errorID = 834 ! negative time increment if (newLoadCase%time < 0.0_pReal) errorID = 834 ! negative time increment
write(6,'(2x,a,f0.3)') 'time: ', newLoadCase%time print'(a,f0.3)', ' time: ', newLoadCase%time
if (newLoadCase%incs < 1) errorID = 835 ! non-positive incs count if (newLoadCase%incs < 1) errorID = 835 ! non-positive incs count
write(6,'(2x,a,i0)') 'increments: ', newLoadCase%incs print'(a,i0)', ' increments: ', newLoadCase%incs
if (newLoadCase%outputfrequency < 1) errorID = 836 ! non-positive result frequency if (newLoadCase%outputfrequency < 1) errorID = 836 ! non-positive result frequency
write(6,'(2x,a,i0)') 'output frequency: ', newLoadCase%outputfrequency print'(a,i0)', ' output frequency: ', newLoadCase%outputfrequency
if (newLoadCase%restartfrequency < 1) errorID = 839 ! non-positive restart frequency if (newLoadCase%restartfrequency < 1) errorID = 839 ! non-positive restart frequency
if (newLoadCase%restartfrequency < huge(0)) & if (newLoadCase%restartfrequency < huge(0)) &
write(6,'(2x,a,i0)') 'restart frequency: ', newLoadCase%restartfrequency print'(a,i0)', ' restart frequency: ', newLoadCase%restartfrequency
if (errorID > 0) call IO_error(error_ID = errorID, ext_msg = loadcase_string) ! exit with error message if (errorID > 0) call IO_error(error_ID = errorID, ext_msg = loadcase_string) ! exit with error message
endif reportAndCheck endif reportAndCheck
loadCases = [loadCases,newLoadCase] ! load case is ok, append it loadCases = [loadCases,newLoadCase] ! load case is ok, append it
@ -341,9 +341,8 @@ program DAMASK_grid
writeHeader: if (interface_restartInc < 1) then writeHeader: if (interface_restartInc < 1) then
open(newunit=statUnit,file=trim(getSolverJobName())//'.sta',form='FORMATTED',status='REPLACE') open(newunit=statUnit,file=trim(getSolverJobName())//'.sta',form='FORMATTED',status='REPLACE')
write(statUnit,'(a)') 'Increment Time CutbackLevel Converged IterationsNeeded' ! statistics file write(statUnit,'(a)') 'Increment Time CutbackLevel Converged IterationsNeeded' ! statistics file
if (debug_grid%contains('basic')) & if (debug_grid%contains('basic')) print'(/,a)', ' header of statistics file written out'
write(6,'(/,a)') ' header of statistics file written out' flush(IO_STDOUT)
flush(6)
else writeHeader else writeHeader
open(newunit=statUnit,file=trim(getSolverJobName())//& open(newunit=statUnit,file=trim(getSolverJobName())//&
'.sta',form='FORMATTED', position='APPEND', status='OLD') '.sta',form='FORMATTED', position='APPEND', status='OLD')
@ -351,7 +350,7 @@ program DAMASK_grid
endif endif
writeUndeformed: if (interface_restartInc < 1) then writeUndeformed: if (interface_restartInc < 1) then
write(6,'(1/,a)') ' ... writing initial configuration to file ........................' print'(/,a)', ' ... writing initial configuration to file ........................'
call CPFEM_results(0,0.0_pReal) call CPFEM_results(0,0.0_pReal)
endif writeUndeformed endif writeUndeformed
@ -397,8 +396,8 @@ program DAMASK_grid
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report begin of new step ! report begin of new step
write(6,'(/,a)') ' ###########################################################################' print'(/,a)', ' ###########################################################################'
write(6,'(1x,a,es12.5,6(a,i0))') & print'(1x,a,es12.5,6(a,i0))', &
'Time', time, & 'Time', time, &
's: Increment ', inc,'/',loadCases(currentLoadCase)%incs,& 's: Increment ', inc,'/',loadCases(currentLoadCase)%incs,&
'-', stepFraction,'/',subStepFactor**cutBackLevel,& '-', stepFraction,'/',subStepFactor**cutBackLevel,&
@ -406,7 +405,7 @@ program DAMASK_grid
write(incInfo,'(4(a,i0))') & write(incInfo,'(4(a,i0))') &
'Increment ',totalIncsCounter,'/',sum(loadCases%incs),& 'Increment ',totalIncsCounter,'/',sum(loadCases%incs),&
'-', stepFraction,'/',subStepFactor**cutBackLevel '-', stepFraction,'/',subStepFactor**cutBackLevel
flush(6) flush(IO_STDOUT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! forward fields ! forward fields
@ -475,7 +474,7 @@ program DAMASK_grid
cutBackLevel = cutBackLevel + 1 cutBackLevel = cutBackLevel + 1
time = time - timeinc ! rewind time time = time - timeinc ! rewind time
timeinc = timeinc/real(subStepFactor,pReal) ! cut timestep timeinc = timeinc/real(subStepFactor,pReal) ! cut timestep
write(6,'(/,a)') ' cutting back ' print'(/,a)', ' cutting back '
else ! no more options to continue else ! no more options to continue
call IO_warning(850) call IO_warning(850)
if (worldrank == 0) close(statUnit) if (worldrank == 0) close(statUnit)
@ -487,14 +486,14 @@ program DAMASK_grid
cutBackLevel = max(0, cutBackLevel - 1) ! try half number of subincs next inc cutBackLevel = max(0, cutBackLevel - 1) ! try half number of subincs next inc
if (all(solres(:)%converged)) then if (all(solres(:)%converged)) then
write(6,'(/,a,i0,a)') ' increment ', totalIncsCounter, ' converged' print'(/,a,i0,a)', ' increment ', totalIncsCounter, ' converged'
else else
write(6,'(/,a,i0,a)') ' increment ', totalIncsCounter, ' NOT converged' print'(/,a,i0,a)', ' increment ', totalIncsCounter, ' NOT converged'
endif; flush(6) endif; flush(IO_STDOUT)
if (mod(inc,loadCases(currentLoadCase)%outputFrequency) == 0) then ! at output frequency if (mod(inc,loadCases(currentLoadCase)%outputFrequency) == 0) then ! at output frequency
write(6,'(1/,a)') ' ... writing results to file ......................................' print'(1/,a)', ' ... writing results to file ......................................'
flush(6) flush(IO_STDOUT)
call CPFEM_results(totalIncsCounter,time) call CPFEM_results(totalIncsCounter,time)
endif endif
if (mod(inc,loadCases(currentLoadCase)%restartFrequency) == 0) then if (mod(inc,loadCases(currentLoadCase)%restartFrequency) == 0) then
@ -510,7 +509,7 @@ program DAMASK_grid
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report summary of whole calculation ! report summary of whole calculation
write(6,'(/,a)') ' ###########################################################################' print'(/,a)', ' ###########################################################################'
if (worldrank == 0) close(statUnit) if (worldrank == 0) close(statUnit)
call quit(0) ! no complains ;) call quit(0) ! no complains ;)

View File

@ -65,7 +65,7 @@ subroutine discretization_grid_init(restart)
integer(C_INTPTR_T) :: & integer(C_INTPTR_T) :: &
devNull, z, z_offset devNull, z, z_offset
write(6,'(/,a)') ' <<<+- discretization_grid init -+>>>'; flush(6) print'(/,a)', ' <<<+- discretization_grid init -+>>>'; flush(IO_STDOUT)
if(index(interface_geomFile,'.vtr') /= 0) then if(index(interface_geomFile,'.vtr') /= 0) then
call readVTR(grid,geomSize,origin,microstructureAt) call readVTR(grid,geomSize,origin,microstructureAt)

View File

@ -22,42 +22,38 @@ module grid_damage_spectral
implicit none implicit none
private private
type, private :: tNumerics type :: tNumerics
integer :: & integer :: &
itmax !< max number of iterations itmax !< maximum number of iterations
real(pReal) :: & real(pReal) :: &
residualStiffness, & !< non-zero residual damage residualStiffness, & !< non-zero residual damage
eps_damage_atol, & !< absolute tolerance for damage evolution eps_damage_atol, & !< absolute tolerance for damage evolution
eps_damage_rtol !< relative tolerance for damage evolution eps_damage_rtol !< relative tolerance for damage evolution
end type tNumerics end type tNumerics
type(tNumerics), private :: num type(tNumerics) :: num
!--------------------------------------------------------------------------------------------------
! derived types
type(tSolutionParams), private :: params
type(tSolutionParams) :: params
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! PETSc data ! PETSc data
SNES, private :: damage_snes SNES :: damage_snes
Vec, private :: solution_vec Vec :: solution_vec
PetscInt, private :: xstart, xend, ystart, yend, zstart, zend PetscInt :: xstart, xend, ystart, yend, zstart, zend
real(pReal), private, dimension(:,:,:), allocatable :: & real(pReal), dimension(:,:,:), allocatable :: &
phi_current, & !< field of current damage phi_current, & !< field of current damage
phi_lastInc, & !< field of previous damage phi_lastInc, & !< field of previous damage
phi_stagInc !< field of staggered damage phi_stagInc !< field of staggered damage
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! reference diffusion tensor, mobility etc. ! reference diffusion tensor, mobility etc.
integer, private :: totalIter = 0 !< total iteration in current increment integer :: totalIter = 0 !< total iteration in current increment
real(pReal), dimension(3,3), private :: K_ref real(pReal), dimension(3,3) :: K_ref
real(pReal), private :: mu_ref real(pReal) :: mu_ref
public :: & public :: &
grid_damage_spectral_init, & grid_damage_spectral_init, &
grid_damage_spectral_solution, & grid_damage_spectral_solution, &
grid_damage_spectral_forward grid_damage_spectral_forward
private :: &
formResidual
contains contains
@ -77,10 +73,10 @@ subroutine grid_damage_spectral_init
character(len=pStringLen) :: & character(len=pStringLen) :: &
snes_type snes_type
write(6,'(/,a)') ' <<<+- grid_spectral_damage init -+>>>' print'(/,a)', ' <<<+- grid_spectral_damage init -+>>>'
write(6,'(/,a)') ' Shanthraj et al., Handbook of Mechanics of Materials, 2019' print*, 'Shanthraj et al., Handbook of Mechanics of Materials, 2019'
write(6,'(a)') ' https://doi.org/10.1007/978-981-10-6855-3_80' print*, 'https://doi.org/10.1007/978-981-10-6855-3_80'
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! read numerical parameters and do sanity checks ! read numerical parameters and do sanity checks
@ -152,8 +148,6 @@ subroutine grid_damage_spectral_init
allocate(phi_stagInc(grid(1),grid(2),grid3), source=1.0_pReal) allocate(phi_stagInc(grid(1),grid(2),grid3), source=1.0_pReal)
call VecSet(solution_vec,1.0_pReal,ierr); CHKERRQ(ierr) call VecSet(solution_vec,1.0_pReal,ierr); CHKERRQ(ierr)
!--------------------------------------------------------------------------------------------------
! damage reference diffusion update
call updateReference call updateReference
end subroutine grid_damage_spectral_init end subroutine grid_damage_spectral_init
@ -210,11 +204,11 @@ function grid_damage_spectral_solution(timeinc,timeinc_old) result(solution)
call VecMin(solution_vec,devNull,phi_min,ierr); CHKERRQ(ierr) call VecMin(solution_vec,devNull,phi_min,ierr); CHKERRQ(ierr)
call VecMax(solution_vec,devNull,phi_max,ierr); CHKERRQ(ierr) call VecMax(solution_vec,devNull,phi_max,ierr); CHKERRQ(ierr)
if (solution%converged) & if (solution%converged) &
write(6,'(/,a)') ' ... nonlocal damage converged .....................................' print'(/,a)', ' ... nonlocal damage converged .....................................'
write(6,'(/,a,f8.6,2x,f8.6,2x,e11.4,/)',advance='no') ' Minimum|Maximum|Delta Damage = ',& write(IO_STDOUT,'(/,a,f8.6,2x,f8.6,2x,e11.4,/)',advance='no') ' Minimum|Maximum|Delta Damage = ',&
phi_min, phi_max, stagNorm phi_min, phi_max, stagNorm
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end function grid_damage_spectral_solution end function grid_damage_spectral_solution

View File

@ -122,7 +122,7 @@ subroutine grid_mech_FEM_init
PetscScalar, pointer, dimension(:,:,:,:) :: & PetscScalar, pointer, dimension(:,:,:,:) :: &
u_current,u_lastInc u_current,u_lastInc
write(6,'(/,a)') ' <<<+- grid_mech_FEM init -+>>>'; flush(6) print'(/,a)', ' <<<+- grid_mech_FEM init -+>>>'; flush(IO_STDOUT)
!----------------------------------------------------------------------------------------------- !-----------------------------------------------------------------------------------------------
! debugging options ! debugging options
@ -130,13 +130,12 @@ subroutine grid_mech_FEM_init
debugRotation = debug_grid%contains('rotation') debugRotation = debug_grid%contains('rotation')
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! read numerical parameter and do sanity checks ! read numerical parameters and do sanity checks
num_grid => config_numerics%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_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_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) num%eps_stress_atol = num_grid%get_asFloat ('eps_stress_atol', defaultVal=1.0e3_pReal)
num%eps_stress_rtol = num_grid%get_asFloat ('eps_stress_rtol', defaultVal=0.01_pReal) num%eps_stress_rtol = num_grid%get_asFloat ('eps_stress_rtol', defaultVal=0.01_pReal)
num%itmin = num_grid%get_asInt ('itmin',defaultVal=1) num%itmin = num_grid%get_asInt ('itmin',defaultVal=1)
num%itmax = num_grid%get_asInt ('itmax',defaultVal=250) num%itmax = num_grid%get_asInt ('itmax',defaultVal=250)
@ -225,7 +224,7 @@ subroutine grid_mech_FEM_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! init fields ! init fields
restartRead: if (interface_restartInc > 0) then restartRead: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading restart data of increment ', interface_restartInc, ' from file' print'(/,a,i0,a)', ' reading restart data of increment ', interface_restartInc, ' from file'
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName) fileHandle = HDF5_openFile(fileName)
@ -254,7 +253,7 @@ subroutine grid_mech_FEM_init
CHKERRQ(ierr) CHKERRQ(ierr)
restartRead2: if (interface_restartInc > 0) then restartRead2: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading more restart data of increment ', interface_restartInc, ' from file' print'(a,i0,a)', ' reading more restart data of increment ', interface_restartInc, ' from file'
call HDF5_read(groupHandle,C_volAvg, 'C_volAvg') call HDF5_read(groupHandle,C_volAvg, 'C_volAvg')
call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc') call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc')
@ -304,11 +303,11 @@ function grid_mech_FEM_solution(incInfoIn,timeinc,timeinc_old,stress_BC,rotation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! solve BVP ! solve BVP
call SNESsolve(mech_snes,PETSC_NULL_VEC,solution_current,ierr);CHKERRQ(ierr) call SNESsolve(mech_snes,PETSC_NULL_VEC,solution_current,ierr); CHKERRQ(ierr)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! check convergence ! check convergence
call SNESGetConvergedReason(mech_snes,reason,ierr);CHKERRQ(ierr) call SNESGetConvergedReason(mech_snes,reason,ierr); CHKERRQ(ierr)
solution%converged = reason > 0 solution%converged = reason > 0
solution%iterationsNeeded = totalIter solution%iterationsNeeded = totalIter
@ -353,7 +352,7 @@ subroutine grid_mech_FEM_forward(cutBack,guess,timeinc,timeinc_old,loadCaseTime,
F_aimDot = merge(stress_BC%maskFloat*(F_aim-F_aim_lastInc)/timeinc_old, 0.0_pReal, guess) F_aimDot = merge(stress_BC%maskFloat*(F_aim-F_aim_lastInc)/timeinc_old, 0.0_pReal, guess)
F_aim_lastInc = F_aim F_aim_lastInc = F_aim
!-------------------------------------------------------------------------------------------------- !-----------------------------------------------------------------------------------------------
! calculate rate for aim ! calculate rate for aim
if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F if (deformation_BC%myType=='l') then ! calculate F_aimDot from given L and current F
F_aimDot = & F_aimDot = &
@ -414,7 +413,7 @@ subroutine grid_mech_FEM_restartWrite
call DMDAVecGetArrayF90(mech_grid,solution_current,u_current,ierr); CHKERRQ(ierr) call DMDAVecGetArrayF90(mech_grid,solution_current,u_current,ierr); CHKERRQ(ierr)
call DMDAVecGetArrayF90(mech_grid,solution_lastInc,u_lastInc,ierr); CHKERRQ(ierr) call DMDAVecGetArrayF90(mech_grid,solution_lastInc,u_lastInc,ierr); CHKERRQ(ierr)
write(6,'(a)') ' writing solver data required for restart to file'; flush(6) print*, 'writing solver data required for restart to file'; flush(IO_STDOUT)
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName,'w') fileHandle = HDF5_openFile(fileName,'w')
@ -476,13 +475,13 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,fnorm,reason,dummy,i
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report ! report
write(6,'(1/,a)') ' ... reporting .............................................................' print'(1/,a)', ' ... reporting .............................................................'
write(6,'(1/,a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', & print'(1/,a,f12.2,a,es8.2,a,es9.2,a)', ' error divergence = ', &
err_div/divTol, ' (',err_div,' / m, tol = ',divTol,')' err_div/divTol, ' (',err_div,' / m, tol = ',divTol,')'
write(6,'(a,f12.2,a,es8.2,a,es9.2,a)') ' error stress BC = ', & print'(a,f12.2,a,es8.2,a,es9.2,a)', ' error stress BC = ', &
err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')' err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')'
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end subroutine converged end subroutine converged
@ -516,13 +515,13 @@ subroutine formResidual(da_local,x_local, &
! begin of new iteration ! begin of new iteration
newIteration: if (totalIter <= PETScIter) then newIteration: if (totalIter <= PETScIter) then
totalIter = totalIter + 1 totalIter = totalIter + 1
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter+1, '≤', num%itmax print'(1x,a,3(a,i0))', trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter+1, '≤', num%itmax
if (debugRotation) & if (debugRotation) &
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.)) ' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim =', transpose(F_aim) ' deformation gradient aim =', transpose(F_aim)
flush(6) flush(IO_STDOUT)
endif newIteration endif newIteration
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -541,7 +540,7 @@ subroutine formResidual(da_local,x_local, &
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! evaluate constitutive response ! evaluate constitutive response
call Utilities_constitutiveResponse(P_current,& call utilities_constitutiveResponse(P_current,&
P_av,C_volAvg,devNull, & P_av,C_volAvg,devNull, &
F,params%timeinc,params%rotation_BC) F,params%timeinc,params%rotation_BC)
call MPI_Allreduce(MPI_IN_PLACE,terminallyIll,1,MPI_LOGICAL,MPI_LOR,PETSC_COMM_WORLD,ierr) call MPI_Allreduce(MPI_IN_PLACE,terminallyIll,1,MPI_LOGICAL,MPI_LOR,PETSC_COMM_WORLD,ierr)

View File

@ -42,8 +42,7 @@ module grid_mech_spectral_basic
type(tNumerics) :: num ! numerics parameters. Better name? type(tNumerics) :: num ! numerics parameters. Better name?
logical, private:: & logical, private :: debugRotation
debugRotation
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! PETSc data ! PETSc data
@ -110,13 +109,13 @@ subroutine grid_mech_spectral_basic_init
character(len=pStringLen) :: & character(len=pStringLen) :: &
fileName fileName
write(6,'(/,a)') ' <<<+- grid_mech_spectral_basic init -+>>>'; flush(6) print'(/,a)', ' <<<+- grid_mech_spectral_basic init -+>>>'; flush(IO_STDOUT)
write(6,'(/,a)') ' Eisenlohr et al., International Journal of Plasticity 46:3753, 2013' print*, 'Eisenlohr et al., International Journal of Plasticity 46:3753, 2013'
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2012.09.012' print*, 'https://doi.org/10.1016/j.ijplas.2012.09.012'//IO_EOL
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:3145, 2015' print*, 'Shanthraj et al., International Journal of Plasticity 66:3145, 2015'
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006' print*, 'https://doi.org/10.1016/j.ijplas.2014.02.006'
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! debugging options ! debugging options
@ -132,7 +131,6 @@ subroutine grid_mech_spectral_basic_init
num%eps_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.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) num%eps_stress_atol = num_grid%get_asFloat ('eps_stress_atol',defaultVal=1.0e3_pReal)
num%eps_stress_rtol = num_grid%get_asFloat ('eps_stress_rtol',defaultVal=0.01_pReal) num%eps_stress_rtol = num_grid%get_asFloat ('eps_stress_rtol',defaultVal=0.01_pReal)
num%itmin = num_grid%get_asInt ('itmin',defaultVal=1) num%itmin = num_grid%get_asInt ('itmin',defaultVal=1)
num%itmax = num_grid%get_asInt ('itmax',defaultVal=250) num%itmax = num_grid%get_asInt ('itmax',defaultVal=250)
@ -186,7 +184,7 @@ subroutine grid_mech_spectral_basic_init
call DMDAVecGetArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! places pointer on PETSc data call DMDAVecGetArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! places pointer on PETSc data
restartRead: if (interface_restartInc > 0) then restartRead: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading restart data of increment ', interface_restartInc, ' from file' print'(/,a,i0,a)', ' reading restart data of increment ', interface_restartInc, ' from file'
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName) fileHandle = HDF5_openFile(fileName)
@ -211,7 +209,7 @@ subroutine grid_mech_spectral_basic_init
call DMDAVecRestoreArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! deassociate pointer call DMDAVecRestoreArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) ! deassociate pointer
restartRead2: if (interface_restartInc > 0) then restartRead2: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading more restart data of increment ', interface_restartInc, ' from file' print'(a,i0,a)', ' reading more restart data of increment ', interface_restartInc, ' from file'
call HDF5_read(groupHandle,C_volAvg, 'C_volAvg') call HDF5_read(groupHandle,C_volAvg, 'C_volAvg')
call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc') call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc')
@ -377,7 +375,7 @@ subroutine grid_mech_spectral_basic_restartWrite
call DMDAVecGetArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr) call DMDAVecGetArrayF90(da,solution_vec,F,ierr); CHKERRQ(ierr)
write(6,'(a)') ' writing solver data required for restart to file'; flush(6) print'(a)', ' writing solver data required for restart to file'; flush(IO_STDOUT)
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName,'w') fileHandle = HDF5_openFile(fileName,'w')
@ -437,13 +435,13 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dumm
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report ! report
write(6,'(1/,a)') ' ... reporting .............................................................' print'(1/,a)', ' ... reporting .............................................................'
write(6,'(1/,a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', & print'(1/,a,f12.2,a,es8.2,a,es9.2,a)', ' error divergence = ', &
err_div/divTol, ' (',err_div,' / m, tol = ',divTol,')' err_div/divTol, ' (',err_div,' / m, tol = ',divTol,')'
write(6,'(a,f12.2,a,es8.2,a,es9.2,a)') ' error stress BC = ', & print'(a,f12.2,a,es8.2,a,es9.2,a)', ' error stress BC = ', &
err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')' err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')'
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end subroutine converged end subroutine converged
@ -475,13 +473,13 @@ subroutine formResidual(in, F, &
! begin of new iteration ! begin of new iteration
newIteration: if (totalIter <= PETScIter) then newIteration: if (totalIter <= PETScIter) then
totalIter = totalIter + 1 totalIter = totalIter + 1
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax print'(1x,a,3(a,i0))', trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
if (debugRotation) & if (debugRotation) &
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.)) ' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim =', transpose(F_aim) ' deformation gradient aim =', transpose(F_aim)
flush(6) flush(IO_STDOUT)
endif newIteration endif newIteration
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -123,10 +123,10 @@ subroutine grid_mech_spectral_polarisation_init
character(len=pStringLen) :: & character(len=pStringLen) :: &
fileName fileName
write(6,'(/,a)') ' <<<+- grid_mech_spectral_polarisation init -+>>>'; flush(6) print'(/,a)', ' <<<+- grid_mech_spectral_polarisation init -+>>>'; flush(IO_STDOUT)
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:3145, 2015' print*, 'Shanthraj et al., International Journal of Plasticity 66:3145, 2015'
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006' print*, 'https://doi.org/10.1016/j.ijplas.2014.02.006'
!------------------------------------------------------------------------------------------------ !------------------------------------------------------------------------------------------------
! debugging options ! debugging options
@ -134,9 +134,8 @@ subroutine grid_mech_spectral_polarisation_init
debugRotation = debug_grid%contains('rotation') debugRotation = debug_grid%contains('rotation')
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! read numerical parameters ! read numerical parameters and do sanity checks
num_grid => config_numerics%get('grid',defaultVal=emptyDict) num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.) 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) 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_div_rtol = num_grid%get_asFloat ('eps_div_rtol', defaultVal=5.0e-4_pReal)
@ -207,7 +206,7 @@ subroutine grid_mech_spectral_polarisation_init
F_tau => FandF_tau(9:17,:,:,:) F_tau => FandF_tau(9:17,:,:,:)
restartRead: if (interface_restartInc > 0) then restartRead: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading restart data of increment ', interface_restartInc, ' from file' print'(/,a,i0,a)', ' reading restart data of increment ', interface_restartInc, ' from file'
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName) fileHandle = HDF5_openFile(fileName)
@ -236,7 +235,7 @@ subroutine grid_mech_spectral_polarisation_init
call DMDAVecRestoreArrayF90(da,solution_vec,FandF_tau,ierr); CHKERRQ(ierr) ! deassociate pointer call DMDAVecRestoreArrayF90(da,solution_vec,FandF_tau,ierr); CHKERRQ(ierr) ! deassociate pointer
restartRead2: if (interface_restartInc > 0) then restartRead2: if (interface_restartInc > 0) then
write(6,'(/,a,i0,a)') ' reading more restart data of increment ', interface_restartInc, ' from file' print'(a,i0,a)', ' reading more restart data of increment ', interface_restartInc, ' from file'
call HDF5_read(groupHandle,C_volAvg, 'C_volAvg') call HDF5_read(groupHandle,C_volAvg, 'C_volAvg')
call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc') call HDF5_read(groupHandle,C_volAvgLastInc,'C_volAvgLastInc')
@ -434,7 +433,7 @@ subroutine grid_mech_spectral_polarisation_restartWrite
F => FandF_tau(0: 8,:,:,:) F => FandF_tau(0: 8,:,:,:)
F_tau => FandF_tau(9:17,:,:,:) F_tau => FandF_tau(9:17,:,:,:)
write(6,'(a)') ' writing solver data required for restart to file'; flush(6) print*, 'writing solver data required for restart to file'; flush(IO_STDOUT)
write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5' write(fileName,'(a,a,i0,a)') trim(getSolverJobName()),'_',worldrank,'.hdf5'
fileHandle = HDF5_openFile(fileName,'w') fileHandle = HDF5_openFile(fileName,'w')
@ -498,15 +497,15 @@ subroutine converged(snes_local,PETScIter,devNull1,devNull2,devNull3,reason,dumm
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report ! report
write(6,'(1/,a)') ' ... reporting .............................................................' print'(1/,a)', ' ... reporting .............................................................'
write(6,'(1/,a,f12.2,a,es8.2,a,es9.2,a)') ' error divergence = ', & print'(1/,a,f12.2,a,es8.2,a,es9.2,a)', ' error divergence = ', &
err_div/divTol, ' (',err_div, ' / m, tol = ',divTol,')' err_div/divTol, ' (',err_div, ' / m, tol = ',divTol,')'
write(6, '(a,f12.2,a,es8.2,a,es9.2,a)') ' error curl = ', & print '(a,f12.2,a,es8.2,a,es9.2,a)', ' error curl = ', &
err_curl/curlTol,' (',err_curl,' -, tol = ',curlTol,')' err_curl/curlTol,' (',err_curl,' -, tol = ',curlTol,')'
write(6, '(a,f12.2,a,es8.2,a,es9.2,a)') ' error BC = ', & print '(a,f12.2,a,es8.2,a,es9.2,a)', ' error stress BC = ', &
err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')' err_BC/BCTol, ' (',err_BC, ' Pa, tol = ',BCTol,')'
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end subroutine converged end subroutine converged
@ -558,13 +557,13 @@ subroutine formResidual(in, FandF_tau, &
! begin of new iteration ! begin of new iteration
newIteration: if (totalIter <= PETScIter) then newIteration: if (totalIter <= PETScIter) then
totalIter = totalIter + 1 totalIter = totalIter + 1
write(6,'(1x,a,3(a,i0))') trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax print'(1x,a,3(a,i0))', trim(incInfo), ' @ Iteration ', num%itmin, '≤',totalIter, '≤', num%itmax
if(debugRotation) & if(debugRotation) &
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.)) ' deformation gradient aim (lab) =', transpose(params%rotation_BC%rotate(F_aim,active=.true.))
write(6,'(/,a,/,3(3(f12.7,1x)/))',advance='no') & write(IO_STDOUT,'(/,a,/,3(3(f12.7,1x)/))',advance='no') &
' deformation gradient aim =', transpose(F_aim) ' deformation gradient aim =', transpose(F_aim)
flush(6) flush(IO_STDOUT)
endif newIteration endif newIteration
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------

View File

@ -23,20 +23,17 @@ module grid_thermal_spectral
implicit none implicit none
private private
!--------------------------------------------------------------------------------------------------
! derived types
type(tSolutionParams) :: params
type :: tNumerics type :: tNumerics
integer :: & integer :: &
itmax !< maximum number of iterations itmax !< maximum number of iterations
real(pReal) :: & real(pReal) :: &
eps_thermal_atol, & !< absolute tolerance for thermal equilibrium eps_thermal_atol, & !< absolute tolerance for thermal equilibrium
eps_thermal_rtol !< relative tolerance for thermal equilibrium eps_thermal_rtol !< relative tolerance for thermal equilibrium
end type tNumerics end type tNumerics
type(tNumerics) :: num type(tNumerics) :: num
type(tSolutionParams) :: params
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! PETSc data ! PETSc data
SNES :: thermal_snes SNES :: thermal_snes
@ -74,13 +71,13 @@ subroutine grid_thermal_spectral_init
class(tNode), pointer :: & class(tNode), pointer :: &
num_grid num_grid
write(6,'(/,a)') ' <<<+- grid_thermal_spectral init -+>>>' print'(/,a)', ' <<<+- grid_thermal_spectral init -+>>>'
write(6,'(/,a)') ' Shanthraj et al., Handbook of Mechanics of Materials, 2019' print*, 'Shanthraj et al., Handbook of Mechanics of Materials, 2019'
write(6,'(a)') ' https://doi.org/10.1007/978-981-10-6855-3_80' print*, 'https://doi.org/10.1007/978-981-10-6855-3_80'
!------------------------------------------------------------------------------------------------- !-------------------------------------------------------------------------------------------------
! read numerical parameter and do sanity checks ! read numerical parameters and do sanity checks
num_grid => config_numerics%get('grid',defaultVal=emptyDict) num_grid => config_numerics%get('grid',defaultVal=emptyDict)
num%itmax = num_grid%get_asInt ('itmax', defaultVal=250) 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_atol = num_grid%get_asFloat ('eps_thermal_atol',defaultVal=1.0e-2_pReal)
@ -94,8 +91,7 @@ subroutine grid_thermal_spectral_init
! set default and user defined options for PETSc ! set default and user defined options for PETSc
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-thermal_snes_type ngmres',ierr) call PETScOptionsInsertString(PETSC_NULL_OPTIONS,'-thermal_snes_type ngmres',ierr)
CHKERRQ(ierr) CHKERRQ(ierr)
call PETScOptionsInsertString(PETSC_NULL_OPTIONS,& call PETScOptionsInsertString(PETSC_NULL_OPTIONS,num_grid%get_asString('petsc_options',defaultVal=''),ierr)
num_grid%get_asString('petsc_options',defaultVal=''),ierr)
CHKERRQ(ierr) CHKERRQ(ierr)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -110,7 +106,7 @@ subroutine grid_thermal_spectral_init
DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point DMDA_STENCIL_BOX, & ! Moore (26) neighborhood around central point
grid(1),grid(2),grid(3), & ! global grid grid(1),grid(2),grid(3), & ! global grid
1, 1, worldsize, & 1, 1, worldsize, &
1, 0, & ! #dof (thermal phase field), ghost boundary width (domain overlap) 1, 0, & ! #dof (T field), ghost boundary width (domain overlap)
[grid(1)],[grid(2)],localK, & ! local grid [grid(1)],[grid(2)],localK, & ! local grid
thermal_grid,ierr) ! handle, error thermal_grid,ierr) ! handle, error
CHKERRQ(ierr) CHKERRQ(ierr)
@ -159,8 +155,6 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old) result(solution)
timeinc_old !< increment in time of last increment timeinc_old !< increment in time of last increment
integer :: i, j, k, cell integer :: i, j, k, cell
type(tSolutionState) :: solution type(tSolutionState) :: solution
class(tNode), pointer :: &
num_grid
PetscInt :: devNull PetscInt :: devNull
PetscReal :: T_min, T_max, stagNorm, solnNorm PetscReal :: T_min, T_max, stagNorm, solnNorm
@ -204,11 +198,11 @@ function grid_thermal_spectral_solution(timeinc,timeinc_old) result(solution)
call VecMin(solution_vec,devNull,T_min,ierr); CHKERRQ(ierr) call VecMin(solution_vec,devNull,T_min,ierr); CHKERRQ(ierr)
call VecMax(solution_vec,devNull,T_max,ierr); CHKERRQ(ierr) call VecMax(solution_vec,devNull,T_max,ierr); CHKERRQ(ierr)
if (solution%converged) & if (solution%converged) &
write(6,'(/,a)') ' ... thermal conduction converged ..................................' print'(/,a)', ' ... thermal conduction converged ..................................'
write(6,'(/,a,f8.4,2x,f8.4,2x,f8.4,/)',advance='no') ' Minimum|Maximum|Delta Temperature / K = ',& write(IO_STDOUT,'(/,a,f8.4,2x,f8.4,2x,f8.4,/)',advance='no') ' Minimum|Maximum|Delta Temperature / K = ',&
T_min, T_max, stagNorm T_min, T_max, stagNorm
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end function grid_thermal_spectral_solution end function grid_thermal_spectral_solution

View File

@ -208,10 +208,10 @@ subroutine spectral_utilities_init
debugPETSc = debug_grid%contains('petsc') debugPETSc = debug_grid%contains('petsc')
if(debugPETSc) write(6,'(3(/,a),/)') & if(debugPETSc) print'(3(/,a),/)', &
' Initializing PETSc with debug options: ', & ' Initializing PETSc with debug options: ', &
trim(PETScDebug), & trim(PETScDebug), &
' add more using the PETSc_Options keyword in numerics.yaml '; flush(6) ' add more using the PETSc_Options keyword in numerics.yaml '; flush(IO_STDOUT)
num_grid => config_numerics%get('grid',defaultVal=emptyDict) num_grid => config_numerics%get('grid',defaultVal=emptyDict)
@ -280,7 +280,7 @@ subroutine spectral_utilities_init
if (pReal /= C_DOUBLE .or. kind(1) /= C_INT) error stop 'C and Fortran datatypes do not match' if (pReal /= C_DOUBLE .or. kind(1) /= C_INT) error stop 'C and Fortran datatypes do not match'
call fftw_set_timelimit(num_grid%get_asFloat('fftw_timelimit',defaultVal=-1.0_pReal)) call fftw_set_timelimit(num_grid%get_asFloat('fftw_timelimit',defaultVal=-1.0_pReal))
if (debugGeneral) write(6,'(/,a)') ' FFTW initialized'; flush(6) print*, 'FFTW initialized'; flush(IO_STDOUT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! MPI allocation ! MPI allocation
@ -506,8 +506,8 @@ subroutine utilities_fourierGammaConvolution(fieldAim)
logical :: err logical :: err
write(6,'(/,a)') ' ... doing gamma convolution ...............................................' print'(/,a)', ' ... doing gamma convolution ...............................................'
flush(6) flush(IO_STDOUT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! do the actual spectral method calculation (mechanical equilibrium) ! do the actual spectral method calculation (mechanical equilibrium)
@ -576,8 +576,8 @@ real(pReal) function utilities_divergenceRMS()
integer :: i, j, k, ierr integer :: i, j, k, ierr
complex(pReal), dimension(3) :: rescaledGeom complex(pReal), dimension(3) :: rescaledGeom
write(6,'(/,a)') ' ... calculating divergence ................................................' print'(/,a)', ' ... calculating divergence ................................................'
flush(6) flush(IO_STDOUT)
rescaledGeom = cmplx(geomSize/scaledGeomSize,0.0_pReal) rescaledGeom = cmplx(geomSize/scaledGeomSize,0.0_pReal)
@ -620,8 +620,8 @@ real(pReal) function utilities_curlRMS()
complex(pReal), dimension(3,3) :: curl_fourier complex(pReal), dimension(3,3) :: curl_fourier
complex(pReal), dimension(3) :: rescaledGeom complex(pReal), dimension(3) :: rescaledGeom
write(6,'(/,a)') ' ... calculating curl ......................................................' print'(/,a)', ' ... calculating curl ......................................................'
flush(6) flush(IO_STDOUT)
rescaledGeom = cmplx(geomSize/scaledGeomSize,0.0_pReal) rescaledGeom = cmplx(geomSize/scaledGeomSize,0.0_pReal)
@ -700,10 +700,10 @@ function utilities_maskedCompliance(rot_BC,mask_stress,C)
temp99_real = math_3333to99(rot_BC%rotate(C)) temp99_real = math_3333to99(rot_BC%rotate(C))
if(debugGeneral) then if(debugGeneral) then
write(6,'(/,a)') ' ... updating masked compliance ............................................' print'(/,a)', ' ... updating masked compliance ............................................'
write(6,'(/,a,/,9(9(2x,f12.7,1x)/))',advance='no') ' Stiffness C (load) / GPa =',& write(IO_STDOUT,'(/,a,/,9(9(2x,f12.7,1x)/))',advance='no') ' Stiffness C (load) / GPa =',&
transpose(temp99_Real)*1.0e-9_pReal transpose(temp99_Real)*1.0e-9_pReal
flush(6) flush(IO_STDOUT)
endif endif
do i = 1,9; do j = 1,9 do i = 1,9; do j = 1,9
@ -723,9 +723,9 @@ function utilities_maskedCompliance(rot_BC,mask_stress,C)
if (debugGeneral .or. errmatinv) then if (debugGeneral .or. errmatinv) then
write(formatString, '(i2)') size_reduced write(formatString, '(i2)') size_reduced
formatString = '(/,a,/,'//trim(formatString)//'('//trim(formatString)//'(2x,es9.2,1x)/))' formatString = '(/,a,/,'//trim(formatString)//'('//trim(formatString)//'(2x,es9.2,1x)/))'
write(6,trim(formatString),advance='no') ' C * S (load) ', & write(IO_STDOUT,trim(formatString),advance='no') ' C * S (load) ', &
transpose(matmul(c_reduced,s_reduced)) transpose(matmul(c_reduced,s_reduced))
write(6,trim(formatString),advance='no') ' S (load) ', transpose(s_reduced) write(IO_STDOUT,trim(formatString),advance='no') ' S (load) ', transpose(s_reduced)
if(errmatinv) call IO_error(error_ID=400,ext_msg='utilities_maskedCompliance') if(errmatinv) call IO_error(error_ID=400,ext_msg='utilities_maskedCompliance')
endif endif
temp99_real = reshape(unpack(reshape(s_reduced,[size_reduced**2]),reshape(mask,[81]),0.0_pReal),[9,9]) temp99_real = reshape(unpack(reshape(s_reduced,[size_reduced**2]),reshape(mask,[81]),0.0_pReal),[9,9])
@ -736,9 +736,9 @@ function utilities_maskedCompliance(rot_BC,mask_stress,C)
utilities_maskedCompliance = math_99to3333(temp99_Real) utilities_maskedCompliance = math_99to3333(temp99_Real)
if(debugGeneral) then if(debugGeneral) then
write(6,'(/,a,/,9(9(2x,f10.5,1x)/),/)',advance='no') & write(IO_STDOUT,'(/,a,/,9(9(2x,f10.5,1x)/),/)',advance='no') &
' Masked Compliance (load) * GPa =', transpose(temp99_Real)*1.0e9_pReal ' Masked Compliance (load) * GPa =', transpose(temp99_Real)*1.0e9_pReal
flush(6) flush(IO_STDOUT)
endif endif
end function utilities_maskedCompliance end function utilities_maskedCompliance
@ -822,8 +822,8 @@ subroutine utilities_constitutiveResponse(P,P_av,C_volAvg,C_minmaxAvg,&
real(pReal) :: dPdF_norm_max, dPdF_norm_min real(pReal) :: dPdF_norm_max, dPdF_norm_min
real(pReal), dimension(2) :: valueAndRank !< pair of min/max norm of dPdF to synchronize min/max of dPdF real(pReal), dimension(2) :: valueAndRank !< pair of min/max norm of dPdF to synchronize min/max of dPdF
write(6,'(/,a)') ' ... evaluating constitutive response ......................................' print'(/,a)', ' ... evaluating constitutive response ......................................'
flush(6) flush(IO_STDOUT)
materialpoint_F = reshape(F,[3,3,1,product(grid(1:2))*grid3]) ! set materialpoint target F to estimated field materialpoint_F = reshape(F,[3,3,1,product(grid(1:2))*grid3]) ! set materialpoint target F to estimated field
@ -833,13 +833,13 @@ subroutine utilities_constitutiveResponse(P,P_av,C_volAvg,C_minmaxAvg,&
P_av = sum(sum(sum(P,dim=5),dim=4),dim=3) * wgt ! average of P P_av = sum(sum(sum(P,dim=5),dim=4),dim=3) * wgt ! average of P
call MPI_Allreduce(MPI_IN_PLACE,P_av,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr) call MPI_Allreduce(MPI_IN_PLACE,P_av,9,MPI_DOUBLE,MPI_SUM,PETSC_COMM_WORLD,ierr)
if (debugRotation) & if (debugRotation) &
write(6,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress (lab) / MPa =',& write(IO_STDOUT,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress (lab) / MPa =',&
transpose(P_av)*1.e-6_pReal transpose(P_av)*1.e-6_pReal
if(present(rotation_BC)) & if(present(rotation_BC)) &
P_av = rotation_BC%rotate(P_av) P_av = rotation_BC%rotate(P_av)
write(6,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress / MPa =',& write(IO_STDOUT,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress / MPa =',&
transpose(P_av)*1.e-6_pReal transpose(P_av)*1.e-6_pReal
flush(6) flush(IO_STDOUT)
dPdF_max = 0.0_pReal dPdF_max = 0.0_pReal
dPdF_norm_max = 0.0_pReal dPdF_norm_max = 0.0_pReal
@ -1095,7 +1095,7 @@ subroutine utilities_saveReferenceStiffness
fileUnit,ierr fileUnit,ierr
if (worldrank == 0) then if (worldrank == 0) then
write(6,'(a)') ' writing reference stiffness data required for restart to file'; flush(6) print'(a)', ' writing reference stiffness data required for restart to file'; flush(IO_STDOUT)
open(newunit=fileUnit, file=getSolverJobName()//'.C_ref',& open(newunit=fileUnit, file=getSolverJobName()//'.C_ref',&
status='replace',access='stream',action='write',iostat=ierr) status='replace',access='stream',action='write',iostat=ierr)
if(ierr /=0) call IO_error(100,ext_msg='could not open file '//getSolverJobName()//'.C_ref') if(ierr /=0) call IO_error(100,ext_msg='could not open file '//getSolverJobName()//'.C_ref')

View File

@ -186,7 +186,7 @@ subroutine homogenization_init
materialpoint_F = materialpoint_F0 ! initialize to identity materialpoint_F = materialpoint_F0 ! initialize to identity
allocate(materialpoint_P(3,3,discretization_nIP,discretization_nElem), source=0.0_pReal) allocate(materialpoint_P(3,3,discretization_nIP,discretization_nElem), source=0.0_pReal)
print'(/,a)', ' <<<+- homogenization init -+>>>'; flush(6) print'(/,a)', ' <<<+- homogenization init -+>>>'; flush(IO_STDOUT)
num%nMPstate = num_homogGeneric%get_asInt ('nMPstate', defaultVal=10) num%nMPstate = num_homogGeneric%get_asInt ('nMPstate', defaultVal=10)
num%subStepMinHomog = num_homogGeneric%get_asFloat('subStepMin', defaultVal=1.0e-3_pReal) num%subStepMinHomog = num_homogGeneric%get_asFloat('subStepMin', defaultVal=1.0e-3_pReal)

View File

@ -95,7 +95,7 @@ module subroutine mech_RGC_init(num_homogMech)
print'(/,a)', ' <<<+- homogenization_mech_rgc init -+>>>' print'(/,a)', ' <<<+- homogenization_mech_rgc init -+>>>'
Ninstance = count(homogenization_type == HOMOGENIZATION_RGC_ID) Ninstance = count(homogenization_type == HOMOGENIZATION_RGC_ID)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
print*, 'Tjahjanto et al., International Journal of Material Forming 2(1):939942, 2009' print*, 'Tjahjanto et al., International Journal of Material Forming 2(1):939942, 2009'
print*, 'https://doi.org/10.1007/s12289-009-0619-1'//IO_EOL print*, 'https://doi.org/10.1007/s12289-009-0619-1'//IO_EOL
@ -247,7 +247,7 @@ module subroutine mech_RGC_partitionDeformation(F,avgF,instance,of)
print'(1x,3(e15.8,1x))',(F(i,j,iGrain), j = 1,3) print'(1x,3(e15.8,1x))',(F(i,j,iGrain), j = 1,3)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
enddo enddo
@ -376,7 +376,7 @@ module procedure mech_RGC_updateState
'@ grain ',stresLoc(3),' in component ',stresLoc(1),stresLoc(2) '@ grain ',stresLoc(3),' in component ',stresLoc(1),stresLoc(2)
print'(a,e15.8,a,i3,a,i2)',' Max residual: ',residMax, & print'(a,e15.8,a,i3,a,i2)',' Max residual: ',residMax, &
' @ iface ',residLoc(1),' in direction ',residLoc(2) ' @ iface ',residLoc(1),' in direction ',residLoc(2)
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -388,7 +388,7 @@ module procedure mech_RGC_updateState
mech_RGC_updateState = .true. mech_RGC_updateState = .true.
#ifdef DEBUG #ifdef DEBUG
if (debugHomog%extensive .and. prm%of_debug == of) & if (debugHomog%extensive .and. prm%of_debug == of) &
print*, '... done and happy'; flush(6) print*, '... done and happy'; flush(IO_STDOUT)
#endif #endif
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -416,7 +416,7 @@ module procedure mech_RGC_updateState
print'(a,e15.8,/)', ' Volume discrepancy: ', dst%volumeDiscrepancy(of) print'(a,e15.8,/)', ' Volume discrepancy: ', dst%volumeDiscrepancy(of)
print'(a,e15.8)', ' Maximum relaxation rate: ', dst%relaxationRate_max(of) print'(a,e15.8)', ' Maximum relaxation rate: ', dst%relaxationRate_max(of)
print'(a,e15.8,/)', ' Average relaxation rate: ', dst%relaxationRate_avg(of) print'(a,e15.8,/)', ' Average relaxation rate: ', dst%relaxationRate_avg(of)
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -429,7 +429,7 @@ module procedure mech_RGC_updateState
#ifdef DEBUG #ifdef DEBUG
if (debugHomog%extensive .and. prm%of_debug == of) & if (debugHomog%extensive .and. prm%of_debug == of) &
print'(a,/)', ' ... broken'; flush(6) print'(a,/)', ' ... broken'; flush(IO_STDOUT)
#endif #endif
return return
@ -437,7 +437,7 @@ module procedure mech_RGC_updateState
else ! proceed with computing the Jacobian and state update else ! proceed with computing the Jacobian and state update
#ifdef DEBUG #ifdef DEBUG
if (debugHomog%extensive .and. prm%of_debug == of) & if (debugHomog%extensive .and. prm%of_debug == of) &
print'(a,/)', ' ... not yet done'; flush(6) print'(a,/)', ' ... not yet done'; flush(IO_STDOUT)
#endif #endif
endif endif
@ -499,7 +499,7 @@ module procedure mech_RGC_updateState
print'(1x,100(e11.4,1x))',(smatrix(i,j), j = 1,3*nIntFaceTot) print'(1x,100(e11.4,1x))',(smatrix(i,j), j = 1,3*nIntFaceTot)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -559,7 +559,7 @@ module procedure mech_RGC_updateState
print'(1x,100(e11.4,1x))',(pmatrix(i,j), j = 1,3*nIntFaceTot) print'(1x,100(e11.4,1x))',(pmatrix(i,j), j = 1,3*nIntFaceTot)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -578,7 +578,7 @@ module procedure mech_RGC_updateState
print'(1x,100(e11.4,1x))',(rmatrix(i,j), j = 1,3*nIntFaceTot) print'(1x,100(e11.4,1x))',(rmatrix(i,j), j = 1,3*nIntFaceTot)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -593,7 +593,7 @@ module procedure mech_RGC_updateState
print'(1x,100(e11.4,1x))',(jmatrix(i,j), j = 1,3*nIntFaceTot) print'(1x,100(e11.4,1x))',(jmatrix(i,j), j = 1,3*nIntFaceTot)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -609,7 +609,7 @@ module procedure mech_RGC_updateState
print'(1x,100(e11.4,1x))',(jnverse(i,j), j = 1,3*nIntFaceTot) print'(1x,100(e11.4,1x))',(jnverse(i,j), j = 1,3*nIntFaceTot)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif
@ -625,7 +625,7 @@ module procedure mech_RGC_updateState
!$OMP CRITICAL (write2out) !$OMP CRITICAL (write2out)
print'(a,i3,a,i3,a)',' RGC_updateState: ip ',ip,' | el ',el,' enforces cutback' print'(a,i3,a,i3,a)',' RGC_updateState: ip ',ip,' | el ',el,' enforces cutback'
print'(a,e15.8)',' due to large relaxation change = ',maxval(abs(drelax)) print'(a,e15.8)',' due to large relaxation change = ',maxval(abs(drelax))
flush(6) flush(IO_STDOUT)
!$OMP END CRITICAL (write2out) !$OMP END CRITICAL (write2out)
endif endif
@ -636,7 +636,7 @@ module procedure mech_RGC_updateState
print'(1x,2(e15.8,1x))', stt%relaxationVector(i,of) print'(1x,2(e15.8,1x))', stt%relaxationVector(i,of)
enddo enddo
print*,' ' print*,' '
flush(6) flush(IO_STDOUT)
endif endif
#endif #endif

View File

@ -40,7 +40,7 @@ module subroutine mech_isostrain_init
print'(/,a)', ' <<<+- homogenization_mech_isostrain init -+>>>' print'(/,a)', ' <<<+- homogenization_mech_isostrain init -+>>>'
Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID) Ninstance = count(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
allocate(param(Ninstance)) ! one container of parameters per instance allocate(param(Ninstance)) ! one container of parameters per instance

View File

@ -21,7 +21,7 @@ module subroutine mech_none_init
print'(/,a)', ' <<<+- homogenization_mech_none init -+>>>' print'(/,a)', ' <<<+- homogenization_mech_none init -+>>>'
Ninstance = count(homogenization_type == HOMOGENIZATION_NONE_ID) Ninstance = count(homogenization_type == HOMOGENIZATION_NONE_ID)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
do h = 1, size(homogenization_type) do h = 1, size(homogenization_type)
if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle if (homogenization_type(h) /= HOMOGENIZATION_NONE_ID) cycle

View File

@ -49,7 +49,7 @@ module function kinematics_cleavage_opening_init(kinematics_length) result(myKin
myKinematics = kinematics_active('cleavage_opening',kinematics_length) myKinematics = kinematics_active('cleavage_opening',kinematics_length)
Ninstance = count(myKinematics) Ninstance = count(myKinematics)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -52,7 +52,7 @@ module function kinematics_slipplane_opening_init(kinematics_length) result(myKi
myKinematics = kinematics_active('slipplane_opening',kinematics_length) myKinematics = kinematics_active('slipplane_opening',kinematics_length)
Ninstance = count(myKinematics) Ninstance = count(myKinematics)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -42,7 +42,7 @@ module function kinematics_thermal_expansion_init(kinematics_length) result(myKi
myKinematics = kinematics_active('thermal_expansion',kinematics_length) myKinematics = kinematics_active('thermal_expansion',kinematics_length)
Ninstance = count(myKinematics) Ninstance = count(myKinematics)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -457,7 +457,7 @@ subroutine lattice_init
phase, & phase, &
elasticity elasticity
print'(/,a)', ' <<<+- lattice init -+>>>'; flush(6) print'(/,a)', ' <<<+- lattice init -+>>>'; flush(IO_STDOUT)
phases => config_material%get('phase') phases => config_material%get('phase')
Nphases = phases%length Nphases = phases%length

View File

@ -70,7 +70,7 @@ subroutine discretization_marc_init
class(tNode), pointer :: & class(tNode), pointer :: &
num_commercialFEM num_commercialFEM
write(6,'(/,a)') ' <<<+- discretization_marc init -+>>>'; flush(6) print'(/,a)', ' <<<+- discretization_marc init -+>>>'; flush(6)
!--------------------------------------------------------------------------------- !---------------------------------------------------------------------------------
! read debug parameters ! read debug parameters
@ -1030,10 +1030,9 @@ pure function IPareaNormal(elem,nElem,connectivity,node)
IPareaNormal(1:3,f,i,e) = math_cross(nodePos(1:3,2) - nodePos(1:3,1), & IPareaNormal(1:3,f,i,e) = math_cross(nodePos(1:3,2) - nodePos(1:3,1), &
nodePos(1:3,3) - nodePos(1:3,1)) nodePos(1:3,3) - nodePos(1:3,1))
case (4) ! 3D 8node case (4) ! 3D 8node
! for this cell type we get the normal of the quadrilateral face as an average of ! Get the normal of the quadrilateral face as the average of four normals of triangular
! four normals of triangular subfaces; since the face consists only of two triangles, ! subfaces. Since the face consists only of two triangles, the sum has to be divided
! the sum has to be divided by two; this whole prcedure tries to compensate for ! by two. This procedure tries to compensate for probable non-planar cell surfaces
! probable non-planar cell surfaces
IPareaNormal(1:3,f,i,e) = 0.0_pReal IPareaNormal(1:3,f,i,e) = 0.0_pReal
do n = 1, m do n = 1, m
IPareaNormal(1:3,f,i,e) = IPareaNormal(1:3,f,i,e) & IPareaNormal(1:3,f,i,e) = IPareaNormal(1:3,f,i,e) &

View File

@ -164,7 +164,7 @@ subroutine material_init(restart)
material_homogenization material_homogenization
character(len=pStringLen) :: sectionName character(len=pStringLen) :: sectionName
print'(/,a)', ' <<<+- material init -+>>>'; flush(6) print'(/,a)', ' <<<+- material init -+>>>'; flush(IO_STDOUT)
phases => config_material%get('phase') phases => config_material%get('phase')
allocate(material_name_phase(phases%length)) allocate(material_name_phase(phases%length))
@ -181,10 +181,10 @@ subroutine material_init(restart)
enddo enddo
call material_parseMicrostructure call material_parseMicrostructure
print*, ' Microstructure parsed' print*, 'Microstructure parsed'
call material_parseHomogenization call material_parseHomogenization
print*, ' Homogenization parsed' print*, 'Homogenization parsed'
if(homogenization_maxNgrains > size(material_phaseAt,1)) call IO_error(148) if(homogenization_maxNgrains > size(material_phaseAt,1)) call IO_error(148)
@ -227,6 +227,7 @@ end subroutine material_init
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @brief parses the homogenization part from the material configuration !> @brief parses the homogenization part from the material configuration
! ToDo: This should be done in homogenization
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine material_parseHomogenization subroutine material_parseHomogenization
@ -320,100 +321,78 @@ end subroutine material_parseHomogenization
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine material_parseMicrostructure subroutine material_parseMicrostructure
class(tNode), pointer :: microstructure, & !> pointer to microstructure list class(tNode), pointer :: microstructures, & !> list of microstructures
constituentsInMicrostructure, & !> pointer to a microstructure list item microstructure, & !> microstructure definition
constituents, & !> pointer to constituents list constituents, & !> list of constituents
constituent, & !> pointer to each constituent constituent, & !> constituent definition
phases, & phases, &
homogenization homogenization
integer, dimension(:), allocatable :: & integer, dimension(:), allocatable :: &
CounterPhase, & counterPhase, &
CounterHomogenization counterHomogenization
real(pReal), dimension(:,:), allocatable :: &
microstructure_fraction !< vol fraction of each constituent in microstrcuture
real(pReal) :: &
frac
integer :: & integer :: &
e, & e, &
i, & i, &
m, & m, &
c, & c, &
microstructure_maxNconstituents maxNconstituents
real(pReal), dimension(4) :: phase_orientation microstructures => config_material%get('microstructure')
if(any(discretization_microstructureAt > microstructures%length)) &
call IO_error(155,ext_msg='More microstructures requested than found in material.yaml')
homogenization => config_material%get('homogenization') allocate(microstructure_Nconstituents(microstructures%length),source=0)
phases => config_material%get('phase') do m = 1, microstructures%length
microstructure => config_material%get('microstructure') microstructure => microstructures%get(m)
allocate(microstructure_Nconstituents(microstructure%length), source = 0) constituents => microstructure%get('constituents')
if(any(discretization_microstructureAt > microstructure%length)) &
call IO_error(155,ext_msg='More microstructures in geometry than sections in material.yaml')
do m = 1, microstructure%length
constituentsInMicrostructure => microstructure%get(m)
constituents => constituentsInMicrostructure%get('constituents')
microstructure_Nconstituents(m) = constituents%length microstructure_Nconstituents(m) = constituents%length
enddo enddo
maxNconstituents = maxval(microstructure_Nconstituents)
microstructure_maxNconstituents = maxval(microstructure_Nconstituents) allocate(material_homogenizationAt(discretization_nElem),source=0)
allocate(microstructure_fraction(microstructure_maxNconstituents,microstructure%length), source =0.0_pReal)
allocate(material_phaseAt(microstructure_maxNconstituents,discretization_nElem), source =0)
allocate(material_orientation0(microstructure_maxNconstituents,discretization_nIP,discretization_nElem))
allocate(material_homogenizationAt(discretization_nElem))
allocate(material_homogenizationMemberAt(discretization_nIP,discretization_nElem),source=0) allocate(material_homogenizationMemberAt(discretization_nIP,discretization_nElem),source=0)
allocate(material_phaseMemberAt(microstructure_maxNconstituents,discretization_nIP,discretization_nElem),source=0) allocate(material_phaseAt(maxNconstituents,discretization_nElem),source=0)
allocate(material_phaseMemberAt(maxNconstituents,discretization_nIP,discretization_nElem),source=0)
allocate(CounterPhase(phases%length),source=0) allocate(material_orientation0(maxNconstituents,discretization_nIP,discretization_nElem))
allocate(CounterHomogenization(homogenization%length),source=0)
do m = 1, microstructure%length phases => config_material%get('phase')
constituentsInMicrostructure => microstructure%get(m) allocate(counterPhase(phases%length),source=0)
constituents => constituentsInMicrostructure%get('constituents') homogenization => config_material%get('homogenization')
allocate(counterHomogenization(homogenization%length),source=0)
do e = 1, discretization_nElem
microstructure => microstructures%get(discretization_microstructureAt(e))
constituents => microstructure%get('constituents')
material_homogenizationAt(e) = homogenization%getIndex(microstructure%get_asString('homogenization'))
do i = 1, discretization_nIP
counterHomogenization(material_homogenizationAt(e)) = counterHomogenization(material_homogenizationAt(e)) + 1
material_homogenizationMemberAt(i,e) = counterHomogenization(material_homogenizationAt(e))
enddo
frac = 0.0_pReal
do c = 1, constituents%length do c = 1, constituents%length
constituent => constituents%get(c) constituent => constituents%get(c)
microstructure_fraction(c,m) = constituent%get_asFloat('fraction') frac = frac + constituent%get_asFloat('fraction')
enddo
if (dNeq(sum(microstructure_fraction(:,m)),1.0_pReal)) call IO_error(153,ext_msg='constituent')
enddo
do e = 1, discretization_nElem material_phaseAt(c,e) = phases%getIndex(constituent%get_asString('phase'))
do i = 1, discretization_nIP do i = 1, discretization_nIP
constituentsInMicrostructure => microstructure%get(discretization_microstructureAt(e)) counterPhase(material_phaseAt(c,e)) = counterPhase(material_phaseAt(c,e)) + 1
constituents => constituentsInMicrostructure%get('constituents') material_phaseMemberAt(c,i,e) = counterPhase(material_phaseAt(c,e))
do c = 1, constituents%length
constituent => constituents%get(c) call material_orientation0(c,i,e)%fromQuaternion(constituent%get_asFloats('orientation',requiredSize=4))
material_phaseAt(c,e) = phases%getIndex(constituent%get_asString('phase'))
phase_orientation = constituent%get_asFloats('orientation')
call material_orientation0(c,i,e)%fromQuaternion(phase_orientation)
enddo 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'))
CounterHomogenization(material_homogenizationAt(e)) = CounterHomogenization(material_homogenizationAt(e)) + 1
material_homogenizationMemberAt(i,e) = CounterHomogenization(material_homogenizationAt(e))
enddo enddo
enddo if (dNeq(frac,1.0_pReal)) call IO_error(153,ext_msg='constituent')
do e = 1, discretization_nElem
do i = 1, discretization_nIP
constituentsInMicrostructure => microstructure%get(discretization_microstructureAt(e))
constituents => constituentsInMicrostructure%get('constituents')
do c = 1, constituents%length
CounterPhase(material_phaseAt(c,e)) = &
CounterPhase(material_phaseAt(c,e)) + 1
material_phaseMemberAt(c,i,e) = CounterPhase(material_phaseAt(c,e))
enddo
enddo
enddo enddo
end subroutine material_parseMicrostructure end subroutine material_parseMicrostructure

View File

@ -91,7 +91,7 @@ subroutine math_init
class(tNode), pointer :: & class(tNode), pointer :: &
num_generic num_generic
print'(/,a)', ' <<<+- math init -+>>>'; flush(6) print'(/,a)', ' <<<+- math init -+>>>'; flush(IO_STDOUT)
num_generic => config_numerics%get('generic',defaultVal=emptyDict) num_generic => config_numerics%get('generic',defaultVal=emptyDict)
randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0) randomSeed = num_generic%get_asInt('random_seed', defaultVal = 0)

View File

@ -78,7 +78,7 @@ program DAMASK_mesh
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! init DAMASK (all modules) ! init DAMASK (all modules)
call CPFEM_initAll call CPFEM_initAll
write(6,'(/,a)') ' <<<+- DAMASK_FEM init -+>>>'; flush(6) print'(/,a)', ' <<<+- DAMASK_mesh init -+>>>'; flush(IO_STDOUT)
!--------------------------------------------------------------------- !---------------------------------------------------------------------
! reading field information from numerics file and do sanity checks ! reading field information from numerics file and do sanity checks
@ -208,30 +208,30 @@ program DAMASK_mesh
errorID = 0 errorID = 0
checkLoadcases: do currentLoadCase = 1, size(loadCases) checkLoadcases: do currentLoadCase = 1, size(loadCases)
write (loadcase_string, '(i0)' ) currentLoadCase write (loadcase_string, '(i0)' ) currentLoadCase
write(6,'(1x,a,i6)') 'load case: ', currentLoadCase print'(a,i0)', ' load case: ', currentLoadCase
if (.not. loadCases(currentLoadCase)%followFormerTrajectory) & if (.not. loadCases(currentLoadCase)%followFormerTrajectory) &
write(6,'(2x,a)') 'drop guessing along trajectory' print'(a)', ' drop guessing along trajectory'
do field = 1, nActiveFields do field = 1, nActiveFields
select case (loadCases(currentLoadCase)%fieldBC(field)%ID) select case (loadCases(currentLoadCase)%fieldBC(field)%ID)
case(FIELD_MECH_ID) case(FIELD_MECH_ID)
write(6,'(2x,a)') 'Field '//trim(FIELD_MECH_label) print'(a)', ' Field '//trim(FIELD_MECH_label)
end select end select
do faceSet = 1, mesh_Nboundaries do faceSet = 1, mesh_Nboundaries
do component = 1, loadCases(currentLoadCase)%fieldBC(field)%nComponents do component = 1, loadCases(currentLoadCase)%fieldBC(field)%nComponents
if (loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%Mask(faceSet)) & if (loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%Mask(faceSet)) &
write(6,'(4x,a,i2,a,i2,a,f12.7)') 'Face ', mesh_boundaries(faceSet), & print'(a,i2,a,i2,a,f12.7)', ' Face ', mesh_boundaries(faceSet), &
' Component ', component, & ' Component ', component, &
' Value ', loadCases(currentLoadCase)%fieldBC(field)% & ' Value ', loadCases(currentLoadCase)%fieldBC(field)% &
componentBC(component)%Value(faceSet) componentBC(component)%Value(faceSet)
enddo enddo
enddo enddo
enddo enddo
write(6,'(2x,a,f12.6)') 'time: ', loadCases(currentLoadCase)%time print'(a,f12.6)', ' time: ', loadCases(currentLoadCase)%time
if (loadCases(currentLoadCase)%incs < 1) errorID = 835 ! non-positive incs count if (loadCases(currentLoadCase)%incs < 1) errorID = 835 ! non-positive incs count
write(6,'(2x,a,i5)') 'increments: ', loadCases(currentLoadCase)%incs print'(a,i5)', ' increments: ', loadCases(currentLoadCase)%incs
if (loadCases(currentLoadCase)%outputfrequency < 1) errorID = 836 ! non-positive result frequency if (loadCases(currentLoadCase)%outputfrequency < 1) errorID = 836 ! non-positive result frequency
write(6,'(2x,a,i5)') 'output frequency: ', & print'(a,i5)', ' output frequency: ', &
loadCases(currentLoadCase)%outputfrequency loadCases(currentLoadCase)%outputfrequency
if (errorID > 0) call IO_error(error_ID = errorID, ext_msg = loadcase_string) ! exit with error message if (errorID > 0) call IO_error(error_ID = errorID, ext_msg = loadcase_string) ! exit with error message
enddo checkLoadcases enddo checkLoadcases
@ -290,8 +290,8 @@ program DAMASK_mesh
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report begin of new step ! report begin of new step
write(6,'(/,a)') ' ###########################################################################' print'(/,a)', ' ###########################################################################'
write(6,'(1x,a,es12.5,6(a,i0))')& print'(1x,a,es12.5,6(a,i0))',&
'Time', time, & 'Time', time, &
's: Increment ', inc, '/', loadCases(currentLoadCase)%incs,& 's: Increment ', inc, '/', loadCases(currentLoadCase)%incs,&
'-', stepFraction, '/', subStepFactor**cutBackLevel,& '-', stepFraction, '/', subStepFactor**cutBackLevel,&
@ -299,7 +299,7 @@ program DAMASK_mesh
write(incInfo,'(4(a,i0))') & write(incInfo,'(4(a,i0))') &
'Increment ',totalIncsCounter,'/',sum(loadCases%incs),& 'Increment ',totalIncsCounter,'/',sum(loadCases%incs),&
'-',stepFraction, '/', subStepFactor**cutBackLevel '-',stepFraction, '/', subStepFactor**cutBackLevel
flush(6) flush(IO_STDOUT)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! forward fields ! forward fields
@ -338,7 +338,7 @@ program DAMASK_mesh
cutBack = .False. cutBack = .False.
if(.not. all(solres(:)%converged .and. solres(:)%stagConverged)) then ! no solution found if(.not. all(solres(:)%converged .and. solres(:)%stagConverged)) then ! no solution found
if (cutBackLevel < maxCutBack) then ! do cut back if (cutBackLevel < maxCutBack) then ! do cut back
write(6,'(/,a)') ' cut back detected' print'(/,a)', ' cut back detected'
cutBack = .True. cutBack = .True.
stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator stepFraction = (stepFraction - 1) * subStepFactor ! adjust to new denominator
cutBackLevel = cutBackLevel + 1 cutBackLevel = cutBackLevel + 1
@ -360,13 +360,13 @@ program DAMASK_mesh
cutBackLevel = max(0, cutBackLevel - 1) ! try half number of subincs next inc cutBackLevel = max(0, cutBackLevel - 1) ! try half number of subincs next inc
if (all(solres(:)%converged)) then if (all(solres(:)%converged)) then
write(6,'(/,a,i0,a)') ' increment ', totalIncsCounter, ' converged' print'(/,a,i0,a)', ' increment ', totalIncsCounter, ' converged'
else else
write(6,'(/,a,i0,a)') ' increment ', totalIncsCounter, ' NOT converged' print'(/,a,i0,a)', ' increment ', totalIncsCounter, ' NOT converged'
endif; flush(6) endif; flush(IO_STDOUT)
if (mod(inc,loadCases(currentLoadCase)%outputFrequency) == 0) then ! at output frequency if (mod(inc,loadCases(currentLoadCase)%outputFrequency) == 0) then ! at output frequency
write(6,'(1/,a)') ' ... writing results to file ......................................' print'(/,a)', ' ... writing results to file ......................................'
call CPFEM_results(totalIncsCounter,time) call CPFEM_results(totalIncsCounter,time)
endif endif
@ -378,7 +378,7 @@ program DAMASK_mesh
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! report summary of whole calculation ! report summary of whole calculation
write(6,'(/,a)') ' ###########################################################################' print'(/,a)', ' ###########################################################################'
if (worldrank == 0) close(statUnit) if (worldrank == 0) close(statUnit)
call quit(0) ! no complains ;) call quit(0) ! no complains ;)

View File

@ -37,7 +37,7 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine FEM_quadrature_init subroutine FEM_quadrature_init
write(6,'(/,a)') ' <<<+- FEM_quadrature init -+>>>'; flush(6) print'(/,a)', ' <<<+- FEM_quadrature init -+>>>'; flush(6)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
! 2D linear ! 2D linear

View File

@ -110,7 +110,7 @@ subroutine FEM_utilities_init
PetscErrorCode :: ierr PetscErrorCode :: ierr
write(6,'(/,a)') ' <<<+- FEM_utilities init -+>>>' print'(/,a)', ' <<<+- FEM_utilities init -+>>>'
num_mesh => config_numerics%get('mesh',defaultVal=emptyDict) num_mesh => config_numerics%get('mesh',defaultVal=emptyDict)
structOrder = num_mesh%get_asInt('structOrder', defaultVal = 2) structOrder = num_mesh%get_asInt('structOrder', defaultVal = 2)
@ -118,11 +118,11 @@ subroutine FEM_utilities_init
debug_mesh => config_debug%get('mesh',defaultVal=emptyList) debug_mesh => config_debug%get('mesh',defaultVal=emptyList)
debugPETSc = debug_mesh%contains('petsc') debugPETSc = debug_mesh%contains('petsc')
if(debugPETSc) write(6,'(3(/,a),/)') & if(debugPETSc) print'(3(/,a),/)', &
' Initializing PETSc with debug options: ', & ' Initializing PETSc with debug options: ', &
trim(PETScDebug), & trim(PETScDebug), &
' add more using the PETSc_Options keyword in numerics.yaml ' ' add more using the PETSc_Options keyword in numerics.yaml '
flush(6) flush(IO_STDOUT)
call PetscOptionsClear(PETSC_NULL_OPTIONS,ierr) call PetscOptionsClear(PETSC_NULL_OPTIONS,ierr)
CHKERRQ(ierr) CHKERRQ(ierr)
if(debugPETSc) call PetscOptionsInsertString(PETSC_NULL_OPTIONS,trim(PETSCDEBUG),ierr) if(debugPETSc) call PetscOptionsInsertString(PETSC_NULL_OPTIONS,trim(PETSCDEBUG),ierr)
@ -158,7 +158,7 @@ subroutine utilities_constitutiveResponse(timeinc,P_av,forwardData)
PetscErrorCode :: ierr PetscErrorCode :: ierr
write(6,'(/,a)') ' ... evaluating constitutive response ......................................' print'(/,a)', ' ... evaluating constitutive response ......................................'
call materialpoint_stressAndItsTangent(.true.,timeinc) ! calculate P field call materialpoint_stressAndItsTangent(.true.,timeinc) ! calculate P field

View File

@ -83,7 +83,7 @@ subroutine discretization_mesh_init(restart)
num_mesh num_mesh
integer :: integrationOrder !< order of quadrature rule required integer :: integrationOrder !< order of quadrature rule required
write(6,'(/,a)') ' <<<+- discretization_mesh init -+>>>' print'(/,a)', ' <<<+- discretization_mesh init -+>>>'
!-------------------------------------------------------------------------------- !--------------------------------------------------------------------------------
! read numerics parameter ! read numerics parameter

View File

@ -110,7 +110,7 @@ subroutine FEM_mech_init(fieldBC)
class(tNode), pointer :: & class(tNode), pointer :: &
num_mesh num_mesh
write(6,'(/,a)') ' <<<+- FEM_mech init -+>>>'; flush(6) print'(/,a)', ' <<<+- FEM_mech init -+>>>'; flush(IO_STDOUT)
!----------------------------------------------------------------------------- !-----------------------------------------------------------------------------
! read numerical parametes and do sanity checks ! read numerical parametes and do sanity checks
@ -318,8 +318,8 @@ type(tSolutionState) function FEM_mech_solution( &
CHKERRQ(ierr) CHKERRQ(ierr)
endif endif
write(6,'(/,a)') ' ===========================================================================' print'(/,a)', ' ==========================================================================='
flush(6) flush(IO_STDOUT)
end function FEM_mech_solution end function FEM_mech_solution
@ -679,12 +679,12 @@ subroutine FEM_mech_converged(snes_local,PETScIter,xnorm,snorm,fnorm,reason,dumm
call SNESConvergedDefault(snes_local,PETScIter,xnorm,snorm,fnorm/divTol,reason,dummy,ierr) call SNESConvergedDefault(snes_local,PETScIter,xnorm,snorm,fnorm/divTol,reason,dummy,ierr)
CHKERRQ(ierr) CHKERRQ(ierr)
if (terminallyIll) reason = SNES_DIVERGED_FUNCTION_DOMAIN if (terminallyIll) reason = SNES_DIVERGED_FUNCTION_DOMAIN
write(6,'(1/,1x,a,a,i0,a,i0,f0.3)') trim(incInfo), & print'(/,1x,a,a,i0,a,i0,f0.3)', trim(incInfo), &
' @ Iteration ',PETScIter,' mechanical residual norm = ', & ' @ Iteration ',PETScIter,' mechanical residual norm = ', &
int(fnorm/divTol),fnorm/divTol-int(fnorm/divTol) int(fnorm/divTol),fnorm/divTol-int(fnorm/divTol)
write(6,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress / MPa =',& write(IO_STDOUT,'(/,a,/,3(3(2x,f12.4,1x)/))',advance='no') ' Piola--Kirchhoff stress / MPa =',&
transpose(P_av)*1.e-6_pReal transpose(P_av)*1.e-6_pReal
flush(6) flush(IO_STDOUT)
end subroutine FEM_mech_converged end subroutine FEM_mech_converged

View File

@ -3,8 +3,8 @@
!> @brief Inquires variables related to parallelization (openMP, MPI) !> @brief Inquires variables related to parallelization (openMP, MPI)
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module parallelization module parallelization
use prec use, intrinsic :: ISO_fortran_env, only: &
use, intrinsic :: iso_fortran_env OUTPUT_UNIT
#ifdef PETSc #ifdef PETSc
#include <petsc/finclude/petscsys.h> #include <petsc/finclude/petscsys.h>
@ -12,6 +12,8 @@ module parallelization
#endif #endif
!$ use OMP_LIB !$ use OMP_LIB
use prec
implicit none implicit none
private private
@ -29,14 +31,14 @@ contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
subroutine parallelization_init subroutine parallelization_init
integer :: err, typeSize integer :: err, typeSize
!$ integer :: got_env, DAMASK_NUM_THREADS, threadLevel !$ integer :: got_env, DAMASK_NUM_THREADS, threadLevel
!$ character(len=6) NumThreadsString !$ character(len=6) NumThreadsString
#ifdef PETSc #ifdef PETSc
PetscErrorCode :: petsc_err PetscErrorCode :: petsc_err
#else #else
print'(/,a)', ' <<<+- parallelization init -+>>>'; flush(6) print'(/,a)', ' <<<+- parallelization init -+>>>'; flush(OUTPUT_UNIT)
#endif #endif
#ifdef PETSc #ifdef PETSc
@ -69,14 +71,10 @@ subroutine parallelization_init
if (typeSize*8 /= storage_size(0.0_pReal)) error stop 'Mismatch between MPI and DAMASK real' if (typeSize*8 /= storage_size(0.0_pReal)) error stop 'Mismatch between MPI and DAMASK real'
#endif #endif
mainProcess: if (worldrank == 0) then if (worldrank /= 0) then
if (output_unit /= 6) error stop 'STDOUT != 6' close(OUTPUT_UNIT) ! disable output
if (error_unit /= 0) error stop 'STDERR != 0' open(OUTPUT_UNIT,file='/dev/null',status='replace') ! close() alone will leave some temp files in cwd
else mainProcess endif
close(6) ! disable output for non-master processes (open 6 to rank specific file for debug)
open(6,file='/dev/null',status='replace') ! close(6) alone will leave some temp files in cwd
endif mainProcess
!$ call get_environment_variable(name='DAMASK_NUM_THREADS',value=NumThreadsString,STATUS=got_env) !$ call get_environment_variable(name='DAMASK_NUM_THREADS',value=NumThreadsString,STATUS=got_env)
!$ if(got_env /= 0) then !$ if(got_env /= 0) then

View File

@ -8,7 +8,7 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
module prec module prec
use, intrinsic :: IEEE_arithmetic use, intrinsic :: IEEE_arithmetic
use, intrinsic :: ISO_C_Binding use, intrinsic :: ISO_C_binding
implicit none implicit none
public public

View File

@ -65,7 +65,7 @@ subroutine results_init(restart)
character(len=pStringLen) :: commandLine character(len=pStringLen) :: commandLine
print'(/,a)', ' <<<+- results init -+>>>'; flush(6) print'(/,a)', ' <<<+- results init -+>>>'; flush(IO_STDOUT)
print*, 'Diehl et al., Integrating Materials and Manufacturing Innovation 6(1):8391, 2017' print*, 'Diehl et al., Integrating Materials and Manufacturing Innovation 6(1):8391, 2017'
print*, 'https://doi.org/10.1007/s40192-017-0084-5'//IO_EOL print*, 'https://doi.org/10.1007/s40192-017-0084-5'//IO_EOL

View File

@ -104,7 +104,7 @@ contains
subroutine rotations_init subroutine rotations_init
call quaternions_init call quaternions_init
print'(/,a)', ' <<<+- rotations init -+>>>'; flush(6) print'(/,a)', ' <<<+- rotations init -+>>>'; flush(IO_STDOUT)
print*, 'Rowenhorst et al., Modelling and Simulation in Materials Science and Engineering 23:083501, 2015' print*, 'Rowenhorst et al., Modelling and Simulation in Materials Science and Engineering 23:083501, 2015'
print*, 'https://doi.org/10.1088/0965-0393/23/8/083501' print*, 'https://doi.org/10.1088/0965-0393/23/8/083501'

View File

@ -53,7 +53,7 @@ module function source_damage_anisoBrittle_init(source_length) result(mySources)
mySources = source_active('damage_anisoBrittle',source_length) mySources = source_active('damage_anisoBrittle',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -47,7 +47,7 @@ module function source_damage_anisoDuctile_init(source_length) result(mySources)
mySources = source_active('damage_anisoDuctile',source_length) mySources = source_active('damage_anisoDuctile',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -43,7 +43,7 @@ module function source_damage_isoBrittle_init(source_length) result(mySources)
mySources = source_active('damage_isoBrittle',source_length) mySources = source_active('damage_isoBrittle',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -45,7 +45,7 @@ module function source_damage_isoDuctile_init(source_length) result(mySources)
mySources = source_active('damage_isoDuctile',source_length) mySources = source_active('damage_isoDuctile',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -41,7 +41,7 @@ module function source_thermal_dissipation_init(source_length) result(mySources)
mySources = source_active('thermal_dissipation',source_length) mySources = source_active('thermal_dissipation',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')

View File

@ -45,7 +45,7 @@ module function source_thermal_externalheat_init(source_length) result(mySources
mySources = source_active('thermal_externalheat',source_length) mySources = source_active('thermal_externalheat',source_length)
Ninstance = count(mySources) Ninstance = count(mySources)
print'(a,i2)', ' # instances: ',Ninstance; flush(6) print'(a,i2)', ' # instances: ',Ninstance; flush(IO_STDOUT)
if(Ninstance == 0) return if(Ninstance == 0) return
phases => config_material%get('phase') phases => config_material%get('phase')