Read numerics.yaml once
This commit is contained in:
parent
c19ed21468
commit
19c44d5e97
|
@ -12,6 +12,8 @@ module config
|
||||||
use IO
|
use IO
|
||||||
use debug
|
use debug
|
||||||
use list
|
use list
|
||||||
|
use YAML_parse
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -24,7 +26,6 @@ module config
|
||||||
config_crystallite
|
config_crystallite
|
||||||
|
|
||||||
type(tPartitionedStringList), public, protected :: &
|
type(tPartitionedStringList), public, protected :: &
|
||||||
config_numerics, &
|
|
||||||
config_debug
|
config_debug
|
||||||
|
|
||||||
character(len=pStringLen), public, protected, allocatable, dimension(:) :: &
|
character(len=pStringLen), public, protected, allocatable, dimension(:) :: &
|
||||||
|
@ -109,13 +110,6 @@ subroutine config_init
|
||||||
call IO_error(160,ext_msg='<texture>')
|
call IO_error(160,ext_msg='<texture>')
|
||||||
|
|
||||||
|
|
||||||
inquire(file='numerics.config', exist=fileExists)
|
|
||||||
if (fileExists) then
|
|
||||||
write(6,'(/,a)') ' reading numerics.config'; flush(6)
|
|
||||||
fileContent = IO_read_ASCII('numerics.config')
|
|
||||||
call parse_debugAndNumericsConfig(config_numerics,fileContent)
|
|
||||||
endif
|
|
||||||
|
|
||||||
inquire(file='debug.config', exist=fileExists)
|
inquire(file='debug.config', exist=fileExists)
|
||||||
if (fileExists) then
|
if (fileExists) then
|
||||||
write(6,'(/,a)') ' reading debug.config'; flush(6)
|
write(6,'(/,a)') ' reading debug.config'; flush(6)
|
||||||
|
@ -140,31 +134,16 @@ recursive function read_materialConfig(fileName,cnt) result(fileContent)
|
||||||
character(len=pStringLen), parameter :: dummy = 'https://damask.mpie.de' !< to fill up remaining array
|
character(len=pStringLen), parameter :: dummy = 'https://damask.mpie.de' !< to fill up remaining array
|
||||||
character(len=:), allocatable :: rawData
|
character(len=:), allocatable :: rawData
|
||||||
integer :: &
|
integer :: &
|
||||||
fileLength, &
|
|
||||||
fileUnit, &
|
|
||||||
startPos, endPos, &
|
startPos, endPos, &
|
||||||
myTotalLines, & !< # lines read from file without include statements
|
myTotalLines, & !< # lines read from file without include statements
|
||||||
l,i, &
|
l,i
|
||||||
myStat
|
|
||||||
logical :: warned
|
logical :: warned
|
||||||
|
|
||||||
if (present(cnt)) then
|
if (present(cnt)) then
|
||||||
if (cnt>10) call IO_error(106,ext_msg=trim(fileName))
|
if (cnt>10) call IO_error(106,ext_msg=trim(fileName))
|
||||||
endif
|
endif
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
rawData = IO_read(fileName) ! read data as stream
|
||||||
! read data as stream
|
|
||||||
inquire(file = fileName, size=fileLength)
|
|
||||||
if (fileLength == 0) then
|
|
||||||
allocate(fileContent(0))
|
|
||||||
return
|
|
||||||
endif
|
|
||||||
open(newunit=fileUnit, file=fileName, access='stream',&
|
|
||||||
status='old', position='rewind', action='read',iostat=myStat)
|
|
||||||
if(myStat /= 0) call IO_error(100,ext_msg=trim(fileName))
|
|
||||||
allocate(character(len=fileLength)::rawData)
|
|
||||||
read(fileUnit) rawData
|
|
||||||
close(fileUnit)
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! count lines to allocate string array
|
! count lines to allocate string array
|
||||||
|
@ -303,9 +282,6 @@ subroutine config_deallocate(what)
|
||||||
case('debug.config')
|
case('debug.config')
|
||||||
call config_debug%free
|
call config_debug%free
|
||||||
|
|
||||||
case('numerics.config')
|
|
||||||
call config_numerics%free
|
|
||||||
|
|
||||||
case default
|
case default
|
||||||
call IO_error(0,ext_msg='config_deallocate')
|
call IO_error(0,ext_msg='config_deallocate')
|
||||||
|
|
||||||
|
|
|
@ -24,6 +24,7 @@ program DAMASK_grid
|
||||||
use grid_damage_spectral
|
use grid_damage_spectral
|
||||||
use grid_thermal_spectral
|
use grid_thermal_spectral
|
||||||
use results
|
use results
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
@ -88,9 +89,12 @@ program DAMASK_grid
|
||||||
|
|
||||||
external :: &
|
external :: &
|
||||||
quit
|
quit
|
||||||
|
class (tNode), pointer :: &
|
||||||
|
num_grid
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! init DAMASK (all modules)
|
! init DAMASK (all modules)
|
||||||
|
|
||||||
call CPFEM_initAll
|
call CPFEM_initAll
|
||||||
write(6,'(/,a)') ' <<<+- DAMASK_spectral init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- DAMASK_spectral init -+>>>'; flush(6)
|
||||||
|
|
||||||
|
@ -107,15 +111,18 @@ program DAMASK_grid
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! assign mechanics solver depending on selected type
|
! assign mechanics solver depending on selected type
|
||||||
select case (trim(config_numerics%getString('spectral_solver',defaultVal='basic')))
|
|
||||||
case ('basic')
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
|
||||||
|
select case (trim(num_grid%get_asString('solver', defaultVal = 'Basic')))
|
||||||
|
case ('Basic')
|
||||||
mech_init => grid_mech_spectral_basic_init
|
mech_init => grid_mech_spectral_basic_init
|
||||||
mech_forward => grid_mech_spectral_basic_forward
|
mech_forward => grid_mech_spectral_basic_forward
|
||||||
mech_solution => grid_mech_spectral_basic_solution
|
mech_solution => grid_mech_spectral_basic_solution
|
||||||
mech_updateCoords => grid_mech_spectral_basic_updateCoords
|
mech_updateCoords => grid_mech_spectral_basic_updateCoords
|
||||||
mech_restartWrite => grid_mech_spectral_basic_restartWrite
|
mech_restartWrite => grid_mech_spectral_basic_restartWrite
|
||||||
|
|
||||||
case ('polarisation')
|
case ('Polarisation')
|
||||||
if(iand(debug_level(debug_spectral),debug_levelBasic)/= 0) &
|
if(iand(debug_level(debug_spectral),debug_levelBasic)/= 0) &
|
||||||
call IO_warning(42, ext_msg='debug Divergence')
|
call IO_warning(42, ext_msg='debug Divergence')
|
||||||
mech_init => grid_mech_spectral_polarisation_init
|
mech_init => grid_mech_spectral_polarisation_init
|
||||||
|
@ -124,7 +131,7 @@ program DAMASK_grid
|
||||||
mech_updateCoords => grid_mech_spectral_polarisation_updateCoords
|
mech_updateCoords => grid_mech_spectral_polarisation_updateCoords
|
||||||
mech_restartWrite => grid_mech_spectral_polarisation_restartWrite
|
mech_restartWrite => grid_mech_spectral_polarisation_restartWrite
|
||||||
|
|
||||||
case ('fem')
|
case ('FEM')
|
||||||
if(iand(debug_level(debug_spectral),debug_levelBasic)/= 0) &
|
if(iand(debug_level(debug_spectral),debug_levelBasic)/= 0) &
|
||||||
call IO_warning(42, ext_msg='debug Divergence')
|
call IO_warning(42, ext_msg='debug Divergence')
|
||||||
mech_init => grid_mech_FEM_init
|
mech_init => grid_mech_FEM_init
|
||||||
|
@ -134,13 +141,14 @@ program DAMASK_grid
|
||||||
mech_restartWrite => grid_mech_FEM_restartWrite
|
mech_restartWrite => grid_mech_FEM_restartWrite
|
||||||
|
|
||||||
case default
|
case default
|
||||||
call IO_error(error_ID = 891, ext_msg = config_numerics%getString('spectral_solver'))
|
call IO_error(error_ID = 891, ext_msg = trim(num_grid%get_asString('solver')))
|
||||||
|
|
||||||
end select
|
end select
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! reading information from load case file and to sanity checks
|
! reading information from load case file and to sanity checks
|
||||||
fileContent = IO_read_ASCII(trim(loadCaseFile))
|
fileContent = IO_readlines(trim(loadCaseFile))
|
||||||
|
if(size(fileContent) == 0) call IO_error(307,ext_msg='No load case specified')
|
||||||
|
|
||||||
allocate (loadCases(0)) ! array of load cases
|
allocate (loadCases(0)) ! array of load cases
|
||||||
do currentLoadCase = 1, size(fileContent)
|
do currentLoadCase = 1, size(fileContent)
|
||||||
|
|
|
@ -21,6 +21,7 @@ module grid_mech_spectral_basic
|
||||||
use homogenization
|
use homogenization
|
||||||
use discretization_grid
|
use discretization_grid
|
||||||
use debug
|
use debug
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -87,6 +88,8 @@ subroutine grid_mech_spectral_basic_init
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
|
class (tNode), pointer :: &
|
||||||
|
num_grid
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
||||||
|
@ -104,7 +107,8 @@ subroutine grid_mech_spectral_basic_init
|
||||||
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
||||||
|
|
||||||
num%update_gamma = config_numerics%getInt('update_gamma',defaultVal=0) > 0
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
num%update_gamma = num_grid%get_asInt('update_gamma',defaultVal=0) > 0 !ToDo: Make boolean
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set default and user defined options for PETSc
|
! set default and user defined options for PETSc
|
||||||
|
|
|
@ -22,6 +22,7 @@ module grid_mech_spectral_polarisation
|
||||||
use homogenization
|
use homogenization
|
||||||
use discretization_grid
|
use discretization_grid
|
||||||
use debug
|
use debug
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -94,6 +95,8 @@ subroutine grid_mech_spectral_polarisation_init
|
||||||
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
real(pReal), dimension(3,3,grid(1),grid(2),grid3) :: P
|
||||||
real(pReal), dimension(3,3) :: &
|
real(pReal), dimension(3,3) :: &
|
||||||
temp33_Real = 0.0_pReal
|
temp33_Real = 0.0_pReal
|
||||||
|
class (tNode), pointer :: &
|
||||||
|
num_grid
|
||||||
|
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
PetscScalar, pointer, dimension(:,:,:,:) :: &
|
||||||
|
@ -110,7 +113,8 @@ subroutine grid_mech_spectral_polarisation_init
|
||||||
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
write(6,'(/,a)') ' Shanthraj et al., International Journal of Plasticity 66:31–45, 2015'
|
||||||
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
write(6,'(a)') ' https://doi.org/10.1016/j.ijplas.2014.02.006'
|
||||||
|
|
||||||
num%update_gamma = config_numerics%getInt('update_gamma',defaultVal=0) > 0
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
|
num%update_gamma = num_grid%get_asInt('update_gamma',defaultVal=0) > 0
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! set default and user defined options for PETSc
|
! set default and user defined options for PETSc
|
||||||
|
|
|
@ -19,6 +19,7 @@ module spectral_utilities
|
||||||
use config
|
use config
|
||||||
use discretization
|
use discretization
|
||||||
use homogenization
|
use homogenization
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -117,7 +118,7 @@ module spectral_utilities
|
||||||
divergence_correction !< scale divergence/curl calculation: [0: no correction, 1: size scaled to 1, 2: size scaled to Npoints]
|
divergence_correction !< scale divergence/curl calculation: [0: no correction, 1: size scaled to 1, 2: size scaled to Npoints]
|
||||||
logical :: &
|
logical :: &
|
||||||
memory_efficient !< calculate gamma operator on the fly
|
memory_efficient !< calculate gamma operator on the fly
|
||||||
character(len=pStringLen) :: &
|
character(len=:), allocatable :: &
|
||||||
spectral_derivative, & !< approximation used for derivatives in Fourier space
|
spectral_derivative, & !< approximation used for derivatives in Fourier space
|
||||||
FFTW_plan_mode, & !< FFTW plan mode, see www.fftw.org
|
FFTW_plan_mode, & !< FFTW plan mode, see www.fftw.org
|
||||||
PETSc_options
|
PETSc_options
|
||||||
|
@ -188,6 +189,8 @@ subroutine utilities_init
|
||||||
scalarSize = 1_C_INTPTR_T, &
|
scalarSize = 1_C_INTPTR_T, &
|
||||||
vecSize = 3_C_INTPTR_T, &
|
vecSize = 3_C_INTPTR_T, &
|
||||||
tensorSize = 9_C_INTPTR_T
|
tensorSize = 9_C_INTPTR_T
|
||||||
|
class (tNode) , pointer :: &
|
||||||
|
num_grid
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- spectral_utilities init -+>>>'
|
write(6,'(/,a)') ' <<<+- spectral_utilities init -+>>>'
|
||||||
|
|
||||||
|
@ -227,11 +230,13 @@ subroutine utilities_init
|
||||||
write(6,'(/,a,3(i12 ))') ' grid a b c: ', grid
|
write(6,'(/,a,3(i12 ))') ' grid a b c: ', grid
|
||||||
write(6,'(a,3(es12.5))') ' size x y z: ', geomSize
|
write(6,'(a,3(es12.5))') ' size x y z: ', geomSize
|
||||||
|
|
||||||
num%memory_efficient = config_numerics%getInt ('memory_efficient', defaultVal=1) > 0
|
num_grid => numerics_root%get('grid',defaultVal=emptyDict)
|
||||||
num%FFTW_timelimit = config_numerics%getFloat ('fftw_timelimit', defaultVal=-1.0_pReal)
|
|
||||||
num%divergence_correction = config_numerics%getInt ('divergence_correction', defaultVal=2)
|
num%memory_efficient = num_grid%get_asInt ('memory_efficient', defaultVal=1) > 0
|
||||||
num%spectral_derivative = config_numerics%getString('spectral_derivative', defaultVal='continuous')
|
num%FFTW_timelimit = num_grid%get_asFloat ('fftw_timelimit', defaultVal=-1.0_pReal)
|
||||||
num%FFTW_plan_mode = config_numerics%getString('fftw_plan_mode', defaultVal='FFTW_MEASURE')
|
num%divergence_correction = num_grid%get_asInt ('divergence_correction', defaultVal=2)
|
||||||
|
num%spectral_derivative = num_grid%get_asString('derivative', defaultVal='continuous')
|
||||||
|
num%FFTW_plan_mode = num_grid%get_asString('fftw_plan_mode', defaultVal='FFTW_MEASURE')
|
||||||
|
|
||||||
if (num%divergence_correction < 0 .or. num%divergence_correction > 2) &
|
if (num%divergence_correction < 0 .or. num%divergence_correction > 2) &
|
||||||
call IO_error(301,ext_msg='divergence_correction')
|
call IO_error(301,ext_msg='divergence_correction')
|
||||||
|
@ -241,7 +246,7 @@ subroutine utilities_init
|
||||||
spectral_derivative_ID = DERIVATIVE_CONTINUOUS_ID
|
spectral_derivative_ID = DERIVATIVE_CONTINUOUS_ID
|
||||||
case ('central_difference')
|
case ('central_difference')
|
||||||
spectral_derivative_ID = DERIVATIVE_CENTRAL_DIFF_ID
|
spectral_derivative_ID = DERIVATIVE_CENTRAL_DIFF_ID
|
||||||
case ('fwbw_difference')
|
case ('FWBW_difference')
|
||||||
spectral_derivative_ID = DERIVATIVE_FWBW_DIFF_ID
|
spectral_derivative_ID = DERIVATIVE_FWBW_DIFF_ID
|
||||||
case default
|
case default
|
||||||
call IO_error(892,ext_msg=trim(num%spectral_derivative))
|
call IO_error(892,ext_msg=trim(num%spectral_derivative))
|
||||||
|
|
|
@ -23,6 +23,7 @@ module homogenization
|
||||||
use damage_local
|
use damage_local
|
||||||
use damage_nonlocal
|
use damage_nonlocal
|
||||||
use results
|
use results
|
||||||
|
use YAML_types
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
private
|
private
|
||||||
|
@ -59,7 +60,9 @@ module homogenization
|
||||||
module subroutine mech_isostrain_init
|
module subroutine mech_isostrain_init
|
||||||
end subroutine mech_isostrain_init
|
end subroutine mech_isostrain_init
|
||||||
|
|
||||||
module subroutine mech_RGC_init
|
module subroutine mech_RGC_init(num_homogMech)
|
||||||
|
class(tNode), pointer, intent(in) :: &
|
||||||
|
num_homogMech
|
||||||
end subroutine mech_RGC_init
|
end subroutine mech_RGC_init
|
||||||
|
|
||||||
|
|
||||||
|
@ -131,9 +134,18 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine homogenization_init
|
subroutine homogenization_init
|
||||||
|
|
||||||
|
class (tNode) , pointer :: &
|
||||||
|
num_homog, &
|
||||||
|
num_homogMech, &
|
||||||
|
num_homogGeneric
|
||||||
|
|
||||||
|
num_homog => numerics_root%get('homogenization',defaultVal=emptyDict)
|
||||||
|
num_homogMech => num_homog%get('mech',defaultVal=emptyDict)
|
||||||
|
num_homogGeneric => num_homog%get('generic',defaultVal=emptyDict)
|
||||||
|
|
||||||
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call mech_none_init
|
if (any(homogenization_type == HOMOGENIZATION_NONE_ID)) call mech_none_init
|
||||||
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call mech_isostrain_init
|
if (any(homogenization_type == HOMOGENIZATION_ISOSTRAIN_ID)) call mech_isostrain_init
|
||||||
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call mech_RGC_init
|
if (any(homogenization_type == HOMOGENIZATION_RGC_ID)) call mech_RGC_init(num_homogMech)
|
||||||
|
|
||||||
if (any(thermal_type == THERMAL_isothermal_ID)) call thermal_isothermal_init
|
if (any(thermal_type == THERMAL_isothermal_ID)) call thermal_isothermal_init
|
||||||
if (any(thermal_type == THERMAL_adiabatic_ID)) call thermal_adiabatic_init
|
if (any(thermal_type == THERMAL_adiabatic_ID)) call thermal_adiabatic_init
|
||||||
|
@ -157,10 +169,12 @@ subroutine homogenization_init
|
||||||
if (debug_g < 1 .or. debug_g > homogenization_Ngrains(material_homogenizationAt(debug_e))) &
|
if (debug_g < 1 .or. debug_g > homogenization_Ngrains(material_homogenizationAt(debug_e))) &
|
||||||
call IO_error(602,ext_msg='constituent', el=debug_e, g=debug_g)
|
call IO_error(602,ext_msg='constituent', el=debug_e, g=debug_g)
|
||||||
|
|
||||||
num%nMPstate = config_numerics%getInt( 'nmpstate', defaultVal=10)
|
num%nMPstate = num_homogGeneric%get_asInt( 'nMPstate', defaultVal=10)
|
||||||
num%subStepMinHomog = config_numerics%getFloat('substepminhomog', defaultVal=1.0e-3_pReal)
|
num%subStepMinHomog = num_homogGeneric%get_asFloat('subStepMin', defaultVal=1.0e-3_pReal)
|
||||||
num%subStepSizeHomog = config_numerics%getFloat('substepsizehomog', defaultVal=0.25_pReal)
|
num%subStepSizeHomog = num_homogGeneric%get_asFloat('subStepSize', defaultVal=0.25_pReal)
|
||||||
num%stepIncreaseHomog = config_numerics%getFloat('stepincreasehomog', defaultVal=1.5_pReal)
|
num%stepIncreaseHomog = num_homogGeneric%get_asFloat('stepIncrease', defaultVal=1.5_pReal)
|
||||||
|
|
||||||
|
|
||||||
if (num%nMPstate < 1) call IO_error(301,ext_msg='nMPstate')
|
if (num%nMPstate < 1) call IO_error(301,ext_msg='nMPstate')
|
||||||
if (num%subStepMinHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepMinHomog')
|
if (num%subStepMinHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepMinHomog')
|
||||||
if (num%subStepSizeHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepSizeHomog')
|
if (num%subStepSizeHomog <= 0.0_pReal) call IO_error(301,ext_msg='subStepSizeHomog')
|
||||||
|
|
|
@ -75,7 +75,10 @@ contains
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
!> @brief allocates all necessary fields, reads information from material configuration file
|
!> @brief allocates all necessary fields, reads information from material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
module subroutine mech_RGC_init
|
module subroutine mech_RGC_init(num_homogMech)
|
||||||
|
|
||||||
|
class(tNode), pointer, intent(in) :: &
|
||||||
|
num_homogMech
|
||||||
|
|
||||||
integer :: &
|
integer :: &
|
||||||
Ninstance, &
|
Ninstance, &
|
||||||
|
@ -83,6 +86,9 @@ module subroutine mech_RGC_init
|
||||||
NofMyHomog, &
|
NofMyHomog, &
|
||||||
sizeState, nIntFaceTot
|
sizeState, nIntFaceTot
|
||||||
|
|
||||||
|
class (tNode), pointer :: &
|
||||||
|
num_RGC
|
||||||
|
|
||||||
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_RGC_label//' init -+>>>'; flush(6)
|
write(6,'(/,a)') ' <<<+- homogenization_'//HOMOGENIZATION_RGC_label//' init -+>>>'; flush(6)
|
||||||
|
|
||||||
write(6,'(/,a)') ' Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
write(6,'(/,a)') ' Tjahjanto et al., International Journal of Material Forming 2(1):939–942, 2009'
|
||||||
|
@ -100,19 +106,22 @@ module subroutine mech_RGC_init
|
||||||
allocate(state0(Ninstance))
|
allocate(state0(Ninstance))
|
||||||
allocate(dependentState(Ninstance))
|
allocate(dependentState(Ninstance))
|
||||||
|
|
||||||
num%atol = config_numerics%getFloat('atol_rgc', defaultVal=1.0e+4_pReal)
|
num_RGC => num_homogMech%get('RGC',defaultVal=emptyDict)
|
||||||
num%rtol = config_numerics%getFloat('rtol_rgc', defaultVal=1.0e-3_pReal)
|
|
||||||
num%absMax = config_numerics%getFloat('amax_rgc', defaultVal=1.0e+10_pReal)
|
num%atol = num_RGC%get_asFloat('atol', defaultVal=1.0e+4_pReal)
|
||||||
num%relMax = config_numerics%getFloat('rmax_rgc', defaultVal=1.0e+2_pReal)
|
num%rtol = num_RGC%get_asFloat('rtol', defaultVal=1.0e-3_pReal)
|
||||||
num%pPert = config_numerics%getFloat('perturbpenalty_rgc', defaultVal=1.0e-7_pReal)
|
num%absMax = num_RGC%get_asFloat('amax', defaultVal=1.0e+10_pReal)
|
||||||
num%xSmoo = config_numerics%getFloat('relvantmismatch_rgc', defaultVal=1.0e-5_pReal)
|
num%relMax = num_RGC%get_asFloat('rmax', defaultVal=1.0e+2_pReal)
|
||||||
num%viscPower = config_numerics%getFloat('viscositypower_rgc', defaultVal=1.0e+0_pReal)
|
num%pPert = num_RGC%get_asFloat('perturbpenalty', defaultVal=1.0e-7_pReal)
|
||||||
num%viscModus = config_numerics%getFloat('viscositymodulus_rgc', defaultVal=0.0e+0_pReal)
|
num%xSmoo = num_RGC%get_asFloat('relvantmismatch', defaultVal=1.0e-5_pReal)
|
||||||
num%refRelaxRate = config_numerics%getFloat('refrelaxationrate_rgc',defaultVal=1.0e-3_pReal)
|
num%viscPower = num_RGC%get_asFloat('viscositypower', defaultVal=1.0e+0_pReal)
|
||||||
num%maxdRelax = config_numerics%getFloat('maxrelaxationrate_rgc',defaultVal=1.0e+0_pReal)
|
num%viscModus = num_RGC%get_asFloat('viscositymodulus', defaultVal=0.0e+0_pReal)
|
||||||
num%maxVolDiscr = config_numerics%getFloat('maxvoldiscrepancy_rgc',defaultVal=1.0e-5_pReal)
|
num%refRelaxRate = num_RGC%get_asFloat('refrelaxationrate',defaultVal=1.0e-3_pReal)
|
||||||
num%volDiscrMod = config_numerics%getFloat('voldiscrepancymod_rgc',defaultVal=1.0e+12_pReal)
|
num%maxdRelax = num_RGC%get_asFloat('maxrelaxationrate',defaultVal=1.0e+0_pReal)
|
||||||
num%volDiscrPow = config_numerics%getFloat('dicrepancypower_rgc', defaultVal=5.0_pReal)
|
num%maxVolDiscr = num_RGC%get_asFloat('maxvoldiscrepancy',defaultVal=1.0e-5_pReal)
|
||||||
|
num%volDiscrMod = num_RGC%get_asFloat('voldiscrepancymod',defaultVal=1.0e+12_pReal)
|
||||||
|
num%volDiscrPow = num_RGC%get_asFloat('dicrepancypower', defaultVal=5.0_pReal)
|
||||||
|
|
||||||
|
|
||||||
if (num%atol <= 0.0_pReal) call IO_error(301,ext_msg='absTol_RGC')
|
if (num%atol <= 0.0_pReal) call IO_error(301,ext_msg='absTol_RGC')
|
||||||
if (num%rtol <= 0.0_pReal) call IO_error(301,ext_msg='relTol_RGC')
|
if (num%rtol <= 0.0_pReal) call IO_error(301,ext_msg='relTol_RGC')
|
||||||
|
|
|
@ -111,6 +111,7 @@ subroutine numerics_init
|
||||||
!$ endif
|
!$ endif
|
||||||
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution
|
!$ call omp_set_num_threads(DAMASK_NumThreadsInt) ! set number of threads for parallel execution
|
||||||
|
|
||||||
|
numerics_root => emptyDict
|
||||||
inquire(file='numerics.yaml', exist=fexist)
|
inquire(file='numerics.yaml', exist=fexist)
|
||||||
|
|
||||||
fileExists: if (fexist) then
|
fileExists: if (fexist) then
|
||||||
|
|
Loading…
Reference in New Issue