Re-written YAML types
Strict typing for YAML New access pattern requires to specify the expected type, i.e. 'scalar', 'list', or 'dict'. This ensures that the node offers the expected functionality instead of polluting 'tNode' with dummy functions which throw error messages if not overwritten. The restructuring of the code allows to hierarchically construct methods without much code duplication. Some aspects of the error messaging system have been improved.
This commit is contained in:
parent
71c686b508
commit
df5487e1a9
|
@ -14,8 +14,8 @@ if (OPTIMIZATION STREQUAL "OFF" OR OPTIMIZATION STREQUAL "DEBUG")
|
|||
elseif (OPTIMIZATION STREQUAL "DEFENSIVE")
|
||||
set (OPTIMIZATION_FLAGS "-O2")
|
||||
elseif (OPTIMIZATION STREQUAL "AGGRESSIVE")
|
||||
set (OPTIMIZATION_FLAGS "-ipo -O3 -fp-model fast=2 -xHost")
|
||||
# -fast = -ipo, -O3, -no-prec-div, -static, -fp-model fast=2, and -xHost"
|
||||
#set (OPTIMIZATION_FLAGS "-ipo -O3 -fp-model fast=2 -xHost") # ifx 2022.0 has problems with YAML types and IPO
|
||||
set (OPTIMIZATION_FLAGS "-O3 -fp-model fast=2 -xHost")
|
||||
endif ()
|
||||
|
||||
# -assume std_mod_proc_name (included in -standard-semantics) causes problems if other modules
|
||||
|
|
|
@ -283,7 +283,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
|
|||
outdatedByNewInc = .false., & !< needs description
|
||||
materialpoint_init_done = .false., & !< remember whether init has been done already
|
||||
debug_basic = .true.
|
||||
class(tNode), pointer :: &
|
||||
type(tList), pointer :: &
|
||||
debug_Marc ! pointer to Marc debug options
|
||||
|
||||
if(debug_basic) then
|
||||
|
@ -307,7 +307,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
|
|||
if (.not. materialpoint_init_done) then
|
||||
materialpoint_init_done = .true.
|
||||
call materialpoint_initAll
|
||||
debug_Marc => config_debug%get('Marc',defaultVal=emptyList)
|
||||
debug_Marc => config_debug%get_list('Marc',defaultVal=emptyList)
|
||||
debug_basic = debug_Marc%contains('basic')
|
||||
endif
|
||||
|
||||
|
|
|
@ -69,7 +69,7 @@ subroutine discretization_Marc_init
|
|||
real(pReal), dimension(:,:,:,:), allocatable :: &
|
||||
unscaledNormals
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_commercialFEM
|
||||
|
||||
|
||||
|
@ -78,7 +78,7 @@ subroutine discretization_Marc_init
|
|||
debug_e = config_debug%get_asInt('element',defaultVal=1)
|
||||
debug_i = config_debug%get_asInt('integrationpoint',defaultVal=1)
|
||||
|
||||
num_commercialFEM => config_numerics%get('commercialFEM',defaultVal = emptyDict)
|
||||
num_commercialFEM => config_numerics%get_dict('commercialFEM',defaultVal = emptyDict)
|
||||
mesh_unitlength = num_commercialFEM%get_asFloat('unitlength',defaultVal=1.0_pReal) ! set physical extent of a length unit in mesh
|
||||
if (mesh_unitlength <= 0.0_pReal) call IO_error(301,'unitlength')
|
||||
|
||||
|
|
|
@ -101,9 +101,10 @@ end subroutine materialpoint_initAll
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine materialpoint_init
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tList), pointer :: &
|
||||
debug_materialpoint
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- materialpoint init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
allocate(materialpoint_cs( 6,discretization_nIPs,discretization_Nelems), source= 0.0_pReal)
|
||||
|
@ -113,7 +114,7 @@ subroutine materialpoint_init
|
|||
!------------------------------------------------------------------------------
|
||||
! read debug options
|
||||
|
||||
debug_materialpoint => config_debug%get('materialpoint',defaultVal=emptyList)
|
||||
debug_materialpoint => config_debug%get_list('materialpoint',defaultVal=emptyList)
|
||||
debugmaterialpoint%basic = debug_materialpoint%contains('basic')
|
||||
debugmaterialpoint%extensive = debug_materialpoint%contains('extensive')
|
||||
debugmaterialpoint%selective = debug_materialpoint%contains('selective')
|
||||
|
|
|
@ -17,7 +17,8 @@ module YAML_parse
|
|||
|
||||
public :: &
|
||||
YAML_parse_init, &
|
||||
YAML_parse_str
|
||||
YAML_parse_str_asList, &
|
||||
YAML_parse_str_asDict
|
||||
|
||||
#ifdef FYAML
|
||||
interface
|
||||
|
@ -53,16 +54,37 @@ end subroutine YAML_parse_init
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Parse a YAML string into a a structure of nodes.
|
||||
!> @brief Parse a YAML string with list as root into a a structure of nodes.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function YAML_parse_str(str) result(node)
|
||||
function YAML_parse_str_asList(str) result(list)
|
||||
|
||||
character(len=*), intent(in) :: str
|
||||
class (tNode), pointer :: node
|
||||
type(tList), pointer :: list
|
||||
|
||||
class(tNode), pointer :: node
|
||||
|
||||
|
||||
node => parse_flow(to_flow(str))
|
||||
list => node%asList()
|
||||
|
||||
end function YAML_parse_str
|
||||
end function YAML_parse_str_asList
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
!> @brief Parse a YAML string with dict as root into a a structure of nodes.
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
function YAML_parse_str_asDict(str) result(dict)
|
||||
|
||||
character(len=*), intent(in) :: str
|
||||
type(tDict), pointer :: dict
|
||||
|
||||
class(tNode), pointer :: node
|
||||
|
||||
|
||||
node => parse_flow(to_flow(str))
|
||||
dict => node%asDict()
|
||||
|
||||
end function YAML_parse_str_asDict
|
||||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -72,9 +94,9 @@ end function YAML_parse_str
|
|||
recursive function parse_flow(YAML_flow) result(node)
|
||||
|
||||
character(len=*), intent(in) :: YAML_flow !< YAML file in flow style
|
||||
class (tNode), pointer :: node
|
||||
class(tNode), pointer :: node
|
||||
|
||||
class (tNode), pointer :: &
|
||||
class(tNode), pointer :: &
|
||||
myVal
|
||||
character(len=:), allocatable :: &
|
||||
flow_string, &
|
||||
|
|
2162
src/YAML_types.f90
2162
src/YAML_types.f90
File diff suppressed because it is too large
Load Diff
|
@ -12,7 +12,7 @@ module config
|
|||
implicit none(type,external)
|
||||
private
|
||||
|
||||
class(tNode), pointer, public :: &
|
||||
type(tDict), pointer, public :: &
|
||||
config_material, &
|
||||
config_numerics, &
|
||||
config_debug
|
||||
|
@ -58,7 +58,7 @@ subroutine parse_material()
|
|||
end if
|
||||
call parallelization_bcast_str(fileContent)
|
||||
|
||||
config_material => YAML_parse_str(fileContent)
|
||||
config_material => YAML_parse_str_asDict(fileContent)
|
||||
|
||||
end subroutine parse_material
|
||||
|
||||
|
@ -88,7 +88,7 @@ subroutine parse_numerics()
|
|||
end if
|
||||
call parallelization_bcast_str(fileContent)
|
||||
|
||||
config_numerics => YAML_parse_str(fileContent)
|
||||
config_numerics => YAML_parse_str_asDict(fileContent)
|
||||
|
||||
end if
|
||||
|
||||
|
@ -120,7 +120,7 @@ subroutine parse_debug()
|
|||
end if
|
||||
call parallelization_bcast_str(fileContent)
|
||||
|
||||
config_debug => YAML_parse_str(fileContent)
|
||||
config_debug => YAML_parse_str_asDict(fileContent)
|
||||
|
||||
end if
|
||||
|
||||
|
|
|
@ -106,15 +106,21 @@ program DAMASK_grid
|
|||
|
||||
external :: &
|
||||
quit
|
||||
class (tNode), pointer :: &
|
||||
num_grid, &
|
||||
class(tNode), pointer :: &
|
||||
tmp
|
||||
type(tDict), pointer :: &
|
||||
config_load, &
|
||||
load_steps, &
|
||||
num_grid, &
|
||||
load_step, &
|
||||
solver, &
|
||||
step_bc, &
|
||||
step_mech, &
|
||||
step_discretization
|
||||
type(tList), pointer :: &
|
||||
#ifdef __INTEL_LLVM_COMPILER
|
||||
tensor, &
|
||||
#endif
|
||||
load_steps
|
||||
character(len=:), allocatable :: &
|
||||
fileContent, fname
|
||||
|
||||
|
@ -130,7 +136,7 @@ program DAMASK_grid
|
|||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! reading field paramters from numerics file and do sanity checks
|
||||
num_grid => config_numerics%get('grid', defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid', defaultVal=emptyDict)
|
||||
stagItMax = num_grid%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
maxCutBack = num_grid%get_asInt('maxCutBack',defaultVal=3)
|
||||
|
||||
|
@ -147,8 +153,8 @@ program DAMASK_grid
|
|||
endif
|
||||
|
||||
call parallelization_bcast_str(fileContent)
|
||||
config_load => YAML_parse_str(fileContent)
|
||||
solver => config_load%get('solver')
|
||||
config_load => YAML_parse_str_asDict(fileContent)
|
||||
solver => config_load%get_dict('solver')
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! assign mechanics solver depending on selected type
|
||||
|
@ -202,34 +208,42 @@ program DAMASK_grid
|
|||
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
load_steps => config_load%get('loadstep')
|
||||
load_steps => config_load%get_list('loadstep')
|
||||
allocate(loadCases(load_steps%length)) ! array of load cases
|
||||
|
||||
do l = 1, load_steps%length
|
||||
|
||||
load_step => load_steps%get(l)
|
||||
step_bc => load_step%get('boundary_conditions')
|
||||
step_mech => step_bc%get('mechanical')
|
||||
load_step => load_steps%get_dict(l)
|
||||
step_bc => load_step%get_dict('boundary_conditions')
|
||||
step_mech => step_bc%get_dict('mechanical')
|
||||
loadCases(l)%stress%myType=''
|
||||
readMech: do m = 1, step_mech%length
|
||||
select case (step_mech%getKey(m))
|
||||
select case (step_mech%key(m))
|
||||
case ('L','dot_F','F') ! assign values for the deformation BC matrix
|
||||
loadCases(l)%deformation%myType = step_mech%getKey(m)
|
||||
call getMaskedTensor(loadCases(l)%deformation%values,loadCases(l)%deformation%mask,step_mech%get(m))
|
||||
loadCases(l)%deformation%myType = step_mech%key(m)
|
||||
#ifdef __INTEL_LLVM_COMPILER
|
||||
tensor => step_mech%get_list(m)
|
||||
call getMaskedTensor(loadCases(l)%deformation%values,loadCases(l)%deformation%mask,tensor)
|
||||
#else
|
||||
call getMaskedTensor(loadCases(l)%deformation%values,loadCases(l)%deformation%mask,step_mech%get_list(m))
|
||||
#endif
|
||||
case ('dot_P','P')
|
||||
loadCases(l)%stress%myType = step_mech%getKey(m)
|
||||
call getMaskedTensor(loadCases(l)%stress%values,loadCases(l)%stress%mask,step_mech%get(m))
|
||||
loadCases(l)%stress%myType = step_mech%key(m)
|
||||
#ifdef __INTEL_LLVM_COMPILER
|
||||
tensor => step_mech%get_list(m)
|
||||
call getMaskedTensor(loadCases(l)%stress%values,loadCases(l)%stress%mask,tensor)
|
||||
#else
|
||||
call getMaskedTensor(loadCases(l)%stress%values,loadCases(l)%stress%mask,step_mech%get_list(m))
|
||||
#endif
|
||||
end select
|
||||
call loadCases(l)%rot%fromAxisAngle(step_mech%get_as1dFloat('R',defaultVal = real([0.0,0.0,1.0,0.0],pReal)),degrees=.true.)
|
||||
enddo readMech
|
||||
if (.not. allocated(loadCases(l)%deformation%myType)) call IO_error(error_ID=837,ext_msg = 'L/dot_F/F missing')
|
||||
|
||||
step_discretization => load_step%get('discretization')
|
||||
if (.not. step_discretization%contains('t')) call IO_error(error_ID=837,ext_msg = 't missing')
|
||||
if (.not. step_discretization%contains('N')) call IO_error(error_ID=837,ext_msg = 'N missing')
|
||||
loadCases(l)%t = step_discretization%get_asFloat('t')
|
||||
loadCases(l)%N = step_discretization%get_asInt ('N')
|
||||
loadCases(l)%r = step_discretization%get_asFloat('r', defaultVal= 1.0_pReal)
|
||||
step_discretization => load_step%get_dict('discretization')
|
||||
loadCases(l)%t = step_discretization%get_asFloat('t')
|
||||
loadCases(l)%N = step_discretization%get_asInt ('N')
|
||||
loadCases(l)%r = step_discretization%get_asFloat('r',defaultVal= 1.0_pReal)
|
||||
|
||||
loadCases(l)%f_restart = load_step%get_asInt('f_restart', defaultVal=huge(0))
|
||||
if (load_step%get_asString('f_out',defaultVal='n/a') == 'none') then
|
||||
|
@ -499,15 +513,15 @@ subroutine getMaskedTensor(values,mask,tensor)
|
|||
|
||||
real(pReal), intent(out), dimension(3,3) :: values
|
||||
logical, intent(out), dimension(3,3) :: mask
|
||||
class (tNode), pointer :: tensor
|
||||
type(tList), pointer :: tensor
|
||||
|
||||
class (tNode), pointer :: row
|
||||
type(tList), pointer :: row
|
||||
integer :: i,j
|
||||
|
||||
|
||||
values = 0.0_pReal
|
||||
do i = 1,3
|
||||
row => tensor%get(i)
|
||||
row => tensor%get_list(i)
|
||||
do j = 1,3
|
||||
mask(i,j) = row%get_asString(j) == 'x'
|
||||
if (.not. mask(i,j)) values(i,j) = row%get_asFloat(j)
|
||||
|
|
|
@ -76,7 +76,7 @@ subroutine grid_damage_spectral_init()
|
|||
Vec :: uBound, lBound
|
||||
integer(MPI_INTEGER_KIND) :: err_MPI
|
||||
PetscErrorCode :: err_PETSc
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_grid, &
|
||||
num_generic
|
||||
character(len=pStringLen) :: &
|
||||
|
@ -89,12 +89,12 @@ subroutine grid_damage_spectral_init()
|
|||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
num%itmax = num_grid%get_asInt ('itmax',defaultVal=250)
|
||||
num%eps_damage_atol = num_grid%get_asFloat ('eps_damage_atol',defaultVal=1.0e-2_pReal)
|
||||
num%eps_damage_rtol = num_grid%get_asFloat ('eps_damage_rtol',defaultVal=1.0e-6_pReal)
|
||||
|
||||
num_generic => config_numerics%get('generic',defaultVal=emptyDict)
|
||||
num_generic => config_numerics%get_dict('generic',defaultVal=emptyDict)
|
||||
num%residualStiffness = num_generic%get_asFloat('residualStiffness', defaultVal=1.0e-6_pReal)
|
||||
|
||||
if (num%residualStiffness < 0.0_pReal) call IO_error(301,ext_msg='residualStiffness')
|
||||
|
|
|
@ -117,22 +117,24 @@ subroutine grid_mechanical_FEM_init
|
|||
u_current,u_lastInc
|
||||
PetscInt, dimension(0:worldsize-1) :: localK
|
||||
integer(HID_T) :: fileHandle, groupHandle
|
||||
class(tNode), pointer :: &
|
||||
num_grid, &
|
||||
type(tDict), pointer :: &
|
||||
num_grid
|
||||
type(tList), pointer :: &
|
||||
debug_grid
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- grid_mechanical_FEM init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! debugging options
|
||||
debug_grid => config_debug%get('grid',defaultVal=emptyList)
|
||||
debug_grid => config_debug%get_list('grid',defaultVal=emptyList)
|
||||
debugRotation = debug_grid%contains('rotation')
|
||||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
|
||||
num%eps_div_atol = num_grid%get_asFloat('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
num%eps_div_rtol = num_grid%get_asFloat('eps_div_rtol', defaultVal=5.0e-4_pReal)
|
||||
|
|
|
@ -118,12 +118,14 @@ subroutine grid_mechanical_spectral_basic_init
|
|||
#else
|
||||
integer :: fileUnit
|
||||
#endif
|
||||
class (tNode), pointer :: &
|
||||
num_grid, &
|
||||
type(tDict), pointer :: &
|
||||
num_grid
|
||||
type(tList), pointer :: &
|
||||
debug_grid
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- grid_mechanical_spectral_basic init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
print'(/,1x,a)', 'P. Eisenlohr et al., International Journal of Plasticity 46:37–53, 2013'
|
||||
|
@ -134,12 +136,12 @@ subroutine grid_mechanical_spectral_basic_init
|
|||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! debugging options
|
||||
debug_grid => config_debug%get('grid',defaultVal=emptyList)
|
||||
debug_grid => config_debug%get_list('grid',defaultVal=emptyList)
|
||||
debugRotation = debug_grid%contains('rotation')
|
||||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
|
||||
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
|
||||
num%eps_div_atol = num_grid%get_asFloat('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
|
|
|
@ -131,8 +131,9 @@ subroutine grid_mechanical_spectral_polarisation_init
|
|||
#else
|
||||
integer :: fileUnit
|
||||
#endif
|
||||
class (tNode), pointer :: &
|
||||
num_grid, &
|
||||
type(tDict), pointer :: &
|
||||
num_grid
|
||||
type(tList), pointer :: &
|
||||
debug_grid
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
|
@ -144,12 +145,12 @@ subroutine grid_mechanical_spectral_polarisation_init
|
|||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! debugging options
|
||||
debug_grid => config_debug%get('grid',defaultVal=emptyList)
|
||||
debug_grid => config_debug%get_list('grid',defaultVal=emptyList)
|
||||
debugRotation = debug_grid%contains('rotation')
|
||||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
|
||||
num%update_gamma = num_grid%get_asBool ('update_gamma', defaultVal=.false.)
|
||||
num%eps_div_atol = num_grid%get_asFloat('eps_div_atol', defaultVal=1.0e-4_pReal)
|
||||
|
|
|
@ -78,7 +78,7 @@ subroutine grid_thermal_spectral_init()
|
|||
integer(MPI_INTEGER_KIND) :: err_MPI
|
||||
PetscErrorCode :: err_PETSc
|
||||
integer(HID_T) :: fileHandle, groupHandle
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_grid
|
||||
|
||||
print'(/,1x,a)', '<<<+- grid_thermal_spectral init -+>>>'
|
||||
|
@ -88,7 +88,7 @@ subroutine grid_thermal_spectral_init()
|
|||
|
||||
!-------------------------------------------------------------------------------------------------
|
||||
! read numerical parameters and do sanity checks
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
num%itmax = num_grid%get_asInt ('itmax', defaultVal=250)
|
||||
num%eps_thermal_atol = num_grid%get_asFloat ('eps_thermal_atol',defaultVal=1.0e-2_pReal)
|
||||
num%eps_thermal_rtol = num_grid%get_asFloat ('eps_thermal_rtol',defaultVal=1.0e-6_pReal)
|
||||
|
|
|
@ -166,9 +166,11 @@ subroutine spectral_utilities_init()
|
|||
tensorSize = 9_C_INTPTR_T
|
||||
character(len=*), parameter :: &
|
||||
PETSCDEBUG = ' -snes_view -snes_monitor '
|
||||
class(tNode) , pointer :: &
|
||||
num_grid, &
|
||||
debug_grid ! pointer to grid debug options
|
||||
type(tDict) , pointer :: &
|
||||
num_grid
|
||||
type(tList) , pointer :: &
|
||||
debug_grid
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- spectral_utilities init -+>>>'
|
||||
|
||||
|
@ -186,9 +188,9 @@ subroutine spectral_utilities_init()
|
|||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! set debugging parameters
|
||||
num_grid => config_numerics%get('grid',defaultVal=emptyDict)
|
||||
num_grid => config_numerics%get_dict('grid',defaultVal=emptyDict)
|
||||
|
||||
debug_grid => config_debug%get('grid',defaultVal=emptyList)
|
||||
debug_grid => config_debug%get_List('grid',defaultVal=emptyList)
|
||||
debugGeneral = debug_grid%contains('basic')
|
||||
debugRotation = debug_grid%contains('rotation')
|
||||
debugPETSc = debug_grid%contains('PETSc')
|
||||
|
|
|
@ -196,7 +196,7 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine homogenization_init()
|
||||
|
||||
class (tNode) , pointer :: &
|
||||
type(tDict) , pointer :: &
|
||||
num_homog, &
|
||||
num_homogGeneric
|
||||
|
||||
|
@ -207,8 +207,8 @@ subroutine homogenization_init()
|
|||
allocate(damageState_h (size(material_name_homogenization)))
|
||||
call parseHomogenization()
|
||||
|
||||
num_homog => config_numerics%get('homogenization',defaultVal=emptyDict)
|
||||
num_homogGeneric => num_homog%get('generic',defaultVal=emptyDict)
|
||||
num_homog => config_numerics%get_dict('homogenization',defaultVal=emptyDict)
|
||||
num_homogGeneric => num_homog%get_dict('generic',defaultVal=emptyDict)
|
||||
|
||||
num%nMPstate = num_homogGeneric%get_asInt('nMPstate',defaultVal=10)
|
||||
if (num%nMPstate < 1) call IO_error(301,ext_msg='nMPstate')
|
||||
|
@ -447,7 +447,7 @@ end subroutine homogenization_restartRead
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine parseHomogenization
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
material_homogenization, &
|
||||
homog, &
|
||||
homogThermal, &
|
||||
|
@ -455,17 +455,17 @@ subroutine parseHomogenization
|
|||
|
||||
integer :: h
|
||||
|
||||
material_homogenization => config_material%get('homogenization')
|
||||
material_homogenization => config_material%get_dict('homogenization')
|
||||
|
||||
allocate(thermal_type(size(material_name_homogenization)),source=THERMAL_UNDEFINED_ID)
|
||||
allocate(thermal_active(size(material_name_homogenization)),source=.false.)
|
||||
allocate(damage_active(size(material_name_homogenization)),source=.false.)
|
||||
|
||||
do h=1, size(material_name_homogenization)
|
||||
homog => material_homogenization%get(h)
|
||||
homog => material_homogenization%get_dict(h)
|
||||
|
||||
if (homog%contains('thermal')) then
|
||||
homogThermal => homog%get('thermal')
|
||||
homogThermal => homog%get_dict('thermal')
|
||||
select case (homogThermal%get_asString('type'))
|
||||
case('pass')
|
||||
thermal_type(h) = THERMAL_PASS_ID
|
||||
|
@ -479,7 +479,7 @@ subroutine parseHomogenization
|
|||
end if
|
||||
|
||||
if (homog%contains('damage')) then
|
||||
homogDamage => homog%get('damage')
|
||||
homogDamage => homog%get_dict('damage')
|
||||
select case (homogDamage%get_asString('type'))
|
||||
case('pass')
|
||||
damage_active(h) = .true.
|
||||
|
|
|
@ -32,7 +32,7 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine damage_init()
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
configHomogenizations, &
|
||||
configHomogenization, &
|
||||
configHomogenizationDamage
|
||||
|
@ -42,17 +42,17 @@ module subroutine damage_init()
|
|||
print'(/,1x,a)', '<<<+- homogenization:damage init -+>>>'
|
||||
|
||||
|
||||
configHomogenizations => config_material%get('homogenization')
|
||||
configHomogenizations => config_material%get_dict('homogenization')
|
||||
allocate(param(configHomogenizations%length))
|
||||
allocate(current(configHomogenizations%length))
|
||||
|
||||
do ho = 1, configHomogenizations%length
|
||||
Nmembers = count(material_homogenizationID == ho)
|
||||
allocate(current(ho)%phi(Nmembers), source=1.0_pReal)
|
||||
configHomogenization => configHomogenizations%get(ho)
|
||||
configHomogenization => configHomogenizations%get_dict(ho)
|
||||
associate(prm => param(ho))
|
||||
if (configHomogenization%contains('damage')) then
|
||||
configHomogenizationDamage => configHomogenization%get('damage')
|
||||
configHomogenizationDamage => configHomogenization%get_dict('damage')
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(configHomogenizationDamage)
|
||||
#else
|
||||
|
|
|
@ -222,7 +222,7 @@ end subroutine mechanical_results
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine parseMechanical()
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
material_homogenization, &
|
||||
homog, &
|
||||
mechanical
|
||||
|
@ -230,14 +230,14 @@ subroutine parseMechanical()
|
|||
integer :: ho
|
||||
|
||||
|
||||
material_homogenization => config_material%get('homogenization')
|
||||
material_homogenization => config_material%get_dict('homogenization')
|
||||
|
||||
allocate(mechanical_type(size(material_name_homogenization)), source=MECHANICAL_UNDEFINED_ID)
|
||||
allocate(output_mechanical(size(material_name_homogenization)))
|
||||
|
||||
do ho=1, size(material_name_homogenization)
|
||||
homog => material_homogenization%get(ho)
|
||||
mechanical => homog%get('mechanical')
|
||||
homog => material_homogenization%get_dict(ho)
|
||||
mechanical => homog%get_dict('mechanical')
|
||||
#if defined(__GFORTRAN__)
|
||||
output_mechanical(ho)%label = output_as1dString(mechanical)
|
||||
#else
|
||||
|
|
|
@ -78,7 +78,7 @@ module subroutine RGC_init()
|
|||
Nmembers, &
|
||||
sizeState, nIntFaceTot
|
||||
|
||||
class (tNode), pointer :: &
|
||||
class(tDict), pointer :: &
|
||||
num_homogenization, &
|
||||
num_mechanical, &
|
||||
num_RGC, & ! pointer to RGC numerics data
|
||||
|
@ -98,15 +98,15 @@ module subroutine RGC_init()
|
|||
print'( 1x,a)', 'https://doi.org/10.1088/0965-0393/18/1/015006'//IO_EOL
|
||||
|
||||
|
||||
material_homogenization => config_material%get('homogenization')
|
||||
material_homogenization => config_material%get_dict('homogenization')
|
||||
allocate(param(material_homogenization%length))
|
||||
allocate(state(material_homogenization%length))
|
||||
allocate(state0(material_homogenization%length))
|
||||
allocate(dependentState(material_homogenization%length))
|
||||
|
||||
num_homogenization => config_numerics%get('homogenization',defaultVal=emptyDict)
|
||||
num_mechanical => num_homogenization%get('mechanical',defaultVal=emptyDict)
|
||||
num_RGC => num_mechanical%get('RGC',defaultVal=emptyDict)
|
||||
num_homogenization => config_numerics%get_dict('homogenization',defaultVal=emptyDict)
|
||||
num_mechanical => num_homogenization%get_dict('mechanical',defaultVal=emptyDict)
|
||||
num_RGC => num_mechanical%get_dict('RGC',defaultVal=emptyDict)
|
||||
|
||||
num%atol = num_RGC%get_asFloat('atol', defaultVal=1.0e+4_pReal)
|
||||
num%rtol = num_RGC%get_asFloat('rtol', defaultVal=1.0e-3_pReal)
|
||||
|
@ -139,8 +139,8 @@ module subroutine RGC_init()
|
|||
|
||||
do ho = 1, size(mechanical_type)
|
||||
if (mechanical_type(ho) /= MECHANICAL_RGC_ID) cycle
|
||||
homog => material_homogenization%get(ho)
|
||||
homogMech => homog%get('mechanical')
|
||||
homog => material_homogenization%get_dict(ho)
|
||||
homogMech => homog%get_dict('mechanical')
|
||||
associate(prm => param(ho), &
|
||||
stt => state(ho), &
|
||||
st0 => state0(ho), &
|
||||
|
|
|
@ -35,7 +35,7 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine thermal_init()
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
configHomogenizations, &
|
||||
configHomogenization, &
|
||||
configHomogenizationThermal
|
||||
|
@ -45,18 +45,18 @@ module subroutine thermal_init()
|
|||
print'(/,1x,a)', '<<<+- homogenization:thermal init -+>>>'
|
||||
|
||||
|
||||
configHomogenizations => config_material%get('homogenization')
|
||||
configHomogenizations => config_material%get_dict('homogenization')
|
||||
allocate(param(configHomogenizations%length))
|
||||
allocate(current(configHomogenizations%length))
|
||||
|
||||
do ho = 1, configHomogenizations%length
|
||||
allocate(current(ho)%T(count(material_homogenizationID==ho)), source=T_ROOM)
|
||||
allocate(current(ho)%dot_T(count(material_homogenizationID==ho)), source=0.0_pReal)
|
||||
configHomogenization => configHomogenizations%get(ho)
|
||||
configHomogenization => configHomogenizations%get_dict(ho)
|
||||
associate(prm => param(ho))
|
||||
|
||||
if (configHomogenization%contains('thermal')) then
|
||||
configHomogenizationThermal => configHomogenization%get('thermal')
|
||||
configHomogenizationThermal => configHomogenization%get_dict('thermal')
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(configHomogenizationThermal)
|
||||
#else
|
||||
|
|
|
@ -83,13 +83,13 @@ end subroutine material_init
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
subroutine parse()
|
||||
|
||||
class(tNode), pointer :: materials, & !> list of materials
|
||||
material, & !> material definition
|
||||
constituents, & !> list of constituents
|
||||
constituent, & !> constituent definition
|
||||
phases, &
|
||||
homogenizations, &
|
||||
homogenization
|
||||
type(tList), pointer :: materials, & !> all materials
|
||||
constituents !> all constituents of a material
|
||||
type(tDict), pointer :: phases, & !> all phases
|
||||
homogenizations, & !> all homogenizations
|
||||
material, & !> material definition
|
||||
constituent, & !> constituent definition
|
||||
homogenization
|
||||
|
||||
class(tItem), pointer :: item
|
||||
integer, dimension(:), allocatable :: &
|
||||
|
@ -107,25 +107,20 @@ subroutine parse()
|
|||
ma
|
||||
|
||||
|
||||
materials => config_material%get('material')
|
||||
phases => config_material%get('phase')
|
||||
homogenizations => config_material%get('homogenization')
|
||||
materials => config_material%get_list('material')
|
||||
phases => config_material%get_dict('phase')
|
||||
homogenizations => config_material%get_dict('homogenization')
|
||||
|
||||
|
||||
if (maxval(discretization_materialAt) > materials%length) &
|
||||
call IO_error(155,ext_msg='More materials requested than found in material.yaml')
|
||||
|
||||
#if defined (__GFORTRAN__)
|
||||
material_name_phase = getKeys(phases)
|
||||
material_name_homogenization = getKeys(homogenizations)
|
||||
#else
|
||||
material_name_phase = phases%Keys()
|
||||
material_name_homogenization = homogenizations%Keys()
|
||||
#endif
|
||||
material_name_phase = phases%keys()
|
||||
material_name_homogenization = homogenizations%keys()
|
||||
|
||||
allocate(homogenization_Nconstituents(homogenizations%length))
|
||||
do ho=1, homogenizations%length
|
||||
homogenization => homogenizations%get(ho)
|
||||
homogenization => homogenizations%get_dict(ho)
|
||||
homogenization_Nconstituents(ho) = homogenization%get_asInt('N_constituents')
|
||||
end do
|
||||
homogenization_maxNconstituents = maxval(homogenization_Nconstituents)
|
||||
|
@ -140,40 +135,33 @@ subroutine parse()
|
|||
allocate( v_of(materials%length,homogenization_maxNconstituents),source=0.0_pReal)
|
||||
|
||||
! parse YAML structure
|
||||
select type(materials)
|
||||
item => materials%first
|
||||
do ma = 1, materials%length
|
||||
material => item%node%asDict()
|
||||
ho_of(ma) = homogenizations%index(material%get_asString('homogenization'))
|
||||
constituents => material%get_list('constituents')
|
||||
|
||||
class is(tList)
|
||||
homogenization => homogenizations%get_dict(ho_of(ma))
|
||||
if (constituents%length /= homogenization%get_asInt('N_constituents')) call IO_error(148)
|
||||
|
||||
item => materials%first
|
||||
do ma = 1, materials%length
|
||||
material => item%node
|
||||
ho_of(ma) = homogenizations%getIndex(material%get_asString('homogenization'))
|
||||
constituents => material%get('constituents')
|
||||
allocate(material_O_0(ma)%data(constituents%length))
|
||||
allocate(material_V_e_0(ma)%data(1:3,1:3,constituents%length))
|
||||
|
||||
homogenization => homogenizations%get(ho_of(ma))
|
||||
if (constituents%length /= homogenization%get_asInt('N_constituents')) call IO_error(148)
|
||||
do co = 1, constituents%length
|
||||
constituent => constituents%get_dict(co)
|
||||
v_of(ma,co) = constituent%get_asFloat('v')
|
||||
ph_of(ma,co) = phases%index(constituent%get_asString('phase'))
|
||||
|
||||
allocate(material_O_0(ma)%data(constituents%length))
|
||||
allocate(material_V_e_0(ma)%data(1:3,1:3,constituents%length))
|
||||
call material_O_0(ma)%data(co)%fromQuaternion(constituent%get_as1dFloat('O',requiredSize=4))
|
||||
material_V_e_0(ma)%data(1:3,1:3,co) = constituent%get_as2dFloat('V_e',defaultVal=math_I3,requiredShape=[3,3])
|
||||
if (any(dNeq(material_V_e_0(ma)%data(1:3,1:3,co),transpose(material_V_e_0(ma)%data(1:3,1:3,co))))) &
|
||||
call IO_error(147)
|
||||
|
||||
do co = 1, constituents%length
|
||||
constituent => constituents%get(co)
|
||||
v_of(ma,co) = constituent%get_asFloat('v')
|
||||
ph_of(ma,co) = phases%getIndex(constituent%get_asString('phase'))
|
||||
|
||||
call material_O_0(ma)%data(co)%fromQuaternion(constituent%get_as1dFloat('O',requiredSize=4))
|
||||
material_V_e_0(ma)%data(1:3,1:3,co) = constituent%get_as2dFloat('V_e',defaultVal=math_I3,requiredShape=[3,3])
|
||||
if (any(dNeq(material_V_e_0(ma)%data(1:3,1:3,co),transpose(material_V_e_0(ma)%data(1:3,1:3,co))))) &
|
||||
call IO_error(147)
|
||||
|
||||
end do
|
||||
if (dNeq(sum(v_of(ma,:)),1.0_pReal,1.e-9_pReal)) call IO_error(153,ext_msg='constituent')
|
||||
|
||||
item => item%next
|
||||
end do
|
||||
|
||||
end select
|
||||
end do
|
||||
if (dNeq(sum(v_of(ma,:)),1.0_pReal,1.e-9_pReal)) call IO_error(153,ext_msg='constituent')
|
||||
|
||||
item => item%next
|
||||
end do
|
||||
|
||||
allocate(counterPhase(phases%length),source=0)
|
||||
allocate(counterHomogenization(homogenizations%length),source=0)
|
||||
|
@ -223,7 +211,7 @@ end subroutine parse
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
function getKeys(dict)
|
||||
|
||||
class(tNode), intent(in) :: dict
|
||||
type(tDict), intent(in) :: dict
|
||||
character(len=:), dimension(:), allocatable :: getKeys
|
||||
character(len=pStringLen), dimension(:), allocatable :: temp
|
||||
|
||||
|
@ -232,7 +220,7 @@ function getKeys(dict)
|
|||
allocate(temp(dict%length))
|
||||
l = 0
|
||||
do i=1, dict%length
|
||||
temp(i) = dict%getKey(i)
|
||||
temp(i) = dict%key(i)
|
||||
l = max(len_trim(temp(i)),l)
|
||||
end do
|
||||
|
||||
|
|
|
@ -87,13 +87,13 @@ subroutine math_init()
|
|||
real(pReal), dimension(4) :: randTest
|
||||
integer :: randSize
|
||||
integer, dimension(:), allocatable :: seed
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_generic
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- math init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
num_generic => config_numerics%get('generic',defaultVal=emptyDict)
|
||||
num_generic => config_numerics%get_dict('generic',defaultVal=emptyDict)
|
||||
|
||||
call random_seed(size=randSize)
|
||||
allocate(seed(randSize))
|
||||
|
|
|
@ -65,7 +65,7 @@ program DAMASK_mesh
|
|||
statUnit = 0, & !< file unit for statistics output
|
||||
stagIter, &
|
||||
component
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_mesh
|
||||
character(len=pStringLen), dimension(:), allocatable :: fileContent
|
||||
character(len=pStringLen) :: &
|
||||
|
@ -90,7 +90,7 @@ program DAMASK_mesh
|
|||
|
||||
!---------------------------------------------------------------------
|
||||
! reading field information from numerics file and do sanity checks
|
||||
num_mesh => config_numerics%get('mesh', defaultVal=emptyDict)
|
||||
num_mesh => config_numerics%get_dict('mesh', defaultVal=emptyDict)
|
||||
stagItMax = num_mesh%get_asInt('maxStaggeredIter',defaultVal=10)
|
||||
maxCutBack = num_mesh%get_asInt('maxCutBack',defaultVal=3)
|
||||
|
||||
|
|
|
@ -93,7 +93,7 @@ contains
|
|||
subroutine FEM_utilities_init
|
||||
|
||||
character(len=pStringLen) :: petsc_optionsOrder
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_mesh, &
|
||||
debug_mesh ! pointer to mesh debug options
|
||||
integer :: &
|
||||
|
@ -107,7 +107,7 @@ subroutine FEM_utilities_init
|
|||
|
||||
print'(/,1x,a)', '<<<+- FEM_utilities init -+>>>'
|
||||
|
||||
num_mesh => config_numerics%get('mesh',defaultVal=emptyDict)
|
||||
num_mesh => config_numerics%get_dict('mesh',defaultVal=emptyDict)
|
||||
|
||||
p_s = num_mesh%get_asInt('p_s',defaultVal = 2)
|
||||
p_i = num_mesh%get_asInt('p_i',defaultVal = p_s)
|
||||
|
@ -117,8 +117,8 @@ subroutine FEM_utilities_init
|
|||
if (p_i < max(1,p_s-1) .or. p_i > p_s) &
|
||||
call IO_error(821,ext_msg='integration order (p_i) out of bounds')
|
||||
|
||||
debug_mesh => config_debug%get('mesh',defaultVal=emptyList)
|
||||
debugPETSc = debug_mesh%contains('PETSc')
|
||||
debug_mesh => config_debug%get_dict('mesh',defaultVal=emptyDict)
|
||||
debugPETSc = debug_mesh%contains('PETSc')
|
||||
|
||||
if(debugPETSc) print'(3(/,1x,a),/)', &
|
||||
'Initializing PETSc with debug options: ', &
|
||||
|
|
|
@ -90,7 +90,7 @@ subroutine discretization_mesh_init(restart)
|
|||
integer(MPI_INTEGER_KIND) :: err_MPI
|
||||
PetscInt, dimension(:), allocatable :: &
|
||||
materialAt
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_mesh
|
||||
integer :: p_i, dim !< integration order (quadrature rule)
|
||||
type(tvec) :: coords_node0
|
||||
|
@ -101,7 +101,7 @@ subroutine discretization_mesh_init(restart)
|
|||
|
||||
!--------------------------------------------------------------------------------
|
||||
! read numerics parameter
|
||||
num_mesh => config_numerics%get('mesh',defaultVal=emptyDict)
|
||||
num_mesh => config_numerics%get_dict('mesh',defaultVal=emptyDict)
|
||||
p_i = num_mesh%get_asInt('p_i',defaultVal = 2)
|
||||
|
||||
!---------------------------------------------------------------------------------
|
||||
|
|
|
@ -126,14 +126,14 @@ subroutine FEM_mechanical_init(fieldBC)
|
|||
character(len=*), parameter :: prefix = 'mechFE_'
|
||||
PetscErrorCode :: err_PETSc
|
||||
real(pReal), dimension(3,3) :: devNull
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_mesh
|
||||
|
||||
print'(/,1x,a)', '<<<+- FEM_mech init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
!-----------------------------------------------------------------------------
|
||||
! read numerical parametes and do sanity checks
|
||||
num_mesh => config_numerics%get('mesh',defaultVal=emptyDict)
|
||||
num_mesh => config_numerics%get_dict('mesh',defaultVal=emptyDict)
|
||||
num%p_i = int(num_mesh%get_asInt('p_i',defaultVal = 2),pPETSCINT)
|
||||
num%itmax = int(num_mesh%get_asInt('itmax',defaultVal=250),pPETSCINT)
|
||||
num%BBarStabilisation = num_mesh%get_asBool('bbarstabilisation',defaultVal = .false.)
|
||||
|
|
|
@ -96,14 +96,14 @@ module phase
|
|||
|
||||
! == cleaned:begin =================================================================================
|
||||
module subroutine mechanical_init(phases)
|
||||
class(tNode), pointer :: phases
|
||||
type(tDict), pointer :: phases
|
||||
end subroutine mechanical_init
|
||||
|
||||
module subroutine damage_init
|
||||
end subroutine damage_init
|
||||
|
||||
module subroutine thermal_init(phases)
|
||||
class(tNode), pointer :: phases
|
||||
type(tDict), pointer :: phases
|
||||
end subroutine thermal_init
|
||||
|
||||
|
||||
|
@ -376,16 +376,16 @@ subroutine phase_init
|
|||
|
||||
integer :: &
|
||||
ph, ce, co, ma
|
||||
class (tNode), pointer :: &
|
||||
debug_constitutive, &
|
||||
materials, &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase
|
||||
type(tList), pointer :: &
|
||||
debug_constitutive
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- phase init -+>>>'; flush(IO_STDOUT)
|
||||
|
||||
debug_constitutive => config_debug%get('phase', defaultVal=emptyList)
|
||||
debug_constitutive => config_debug%get_list('phase', defaultVal=emptyList)
|
||||
debugConstitutive%basic = debug_constitutive%contains('basic')
|
||||
debugConstitutive%extensive = debug_constitutive%contains('extensive')
|
||||
debugConstitutive%selective = debug_constitutive%contains('selective')
|
||||
|
@ -394,8 +394,7 @@ subroutine phase_init
|
|||
debugConstitutive%grain = config_debug%get_asInt('constituent', defaultVal = 1)
|
||||
|
||||
|
||||
materials => config_material%get('material')
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
|
||||
allocate(phase_lattice(phases%length))
|
||||
allocate(phase_cOverA(phases%length),source=-1.0_pReal)
|
||||
|
@ -403,7 +402,7 @@ subroutine phase_init
|
|||
allocate(phase_O_0(phases%length))
|
||||
|
||||
do ph = 1,phases%length
|
||||
phase => phases%get(ph)
|
||||
phase => phases%get_dict(ph)
|
||||
phase_lattice(ph) = phase%get_asString('lattice')
|
||||
if (all(phase_lattice(ph) /= ['cF','cI','hP','tI'])) &
|
||||
call IO_error(130,ext_msg='phase_init: '//phase%get_asString('lattice'))
|
||||
|
@ -536,13 +535,13 @@ subroutine crystallite_init()
|
|||
ip, & !< counter in integration point loop
|
||||
el, & !< counter in element loop
|
||||
en, ph
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_crystallite, &
|
||||
phases
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
|
||||
num_crystallite => config_numerics%get('crystallite',defaultVal=emptyDict)
|
||||
num_crystallite => config_numerics%get_dict('crystallite',defaultVal=emptyDict)
|
||||
|
||||
num%subStepMinCryst = num_crystallite%get_asFloat ('subStepMin', defaultVal=1.0e-3_pReal)
|
||||
num%subStepSizeCryst = num_crystallite%get_asFloat ('subStepSize', defaultVal=0.25_pReal)
|
||||
|
@ -570,7 +569,7 @@ subroutine crystallite_init()
|
|||
|
||||
if (extmsg /= '') call IO_error(301,ext_msg=trim(extmsg))
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
|
||||
!$OMP PARALLEL DO PRIVATE(ce,ph,en)
|
||||
do el = 1, discretization_Nelems
|
||||
|
|
|
@ -77,19 +77,20 @@ module subroutine damage_init
|
|||
integer :: &
|
||||
ph, &
|
||||
Nmembers
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, &
|
||||
source
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
logical:: damage_active
|
||||
|
||||
print'(/,1x,a)', '<<<+- phase:damage init -+>>>'
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
|
||||
allocate(current(phases%length))
|
||||
allocate(damageState (phases%length))
|
||||
allocate(damageState(phases%length))
|
||||
allocate(param(phases%length))
|
||||
|
||||
damage_active = .false.
|
||||
|
@ -99,12 +100,12 @@ module subroutine damage_init
|
|||
|
||||
allocate(current(ph)%phi(Nmembers),source=1.0_pReal)
|
||||
|
||||
phase => phases%get(ph)
|
||||
sources => phase%get('damage',defaultVal=emptyList)
|
||||
phase => phases%get_dict(ph)
|
||||
sources => phase%get_list('damage',defaultVal=emptyList)
|
||||
if (sources%length > 1) error stop
|
||||
if (sources%length == 1) then
|
||||
damage_active = .true.
|
||||
source => sources%get(1)
|
||||
source => sources%get_dict(1)
|
||||
param(ph)%mu = source%get_asFloat('mu')
|
||||
param(ph)%l_c = source%get_asFloat('l_c')
|
||||
end if
|
||||
|
@ -440,19 +441,20 @@ function source_active(source_label) result(active_source)
|
|||
character(len=*), intent(in) :: source_label !< name of source mechanism
|
||||
logical, dimension(:), allocatable :: active_source
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, &
|
||||
src
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
integer :: ph
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(active_source(phases%length))
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
sources => phase%get('damage',defaultVal=emptyList)
|
||||
src => sources%get(1)
|
||||
phase => phases%get_dict(ph)
|
||||
sources => phase%get_list('damage',defaultVal=emptyList)
|
||||
src => sources%get_dict(1)
|
||||
active_source(ph) = src%get_asString('type',defaultVal = 'x') == source_label
|
||||
end do
|
||||
|
||||
|
|
|
@ -35,11 +35,12 @@ module function anisobrittle_init() result(mySources)
|
|||
|
||||
logical, dimension(:), allocatable :: mySources
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, &
|
||||
src
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
integer :: Nmembers,ph
|
||||
integer, dimension(:), allocatable :: N_cl
|
||||
character(len=pStringLen) :: extmsg = ''
|
||||
|
@ -52,17 +53,17 @@ module function anisobrittle_init() result(mySources)
|
|||
print'(/,a,i0)', ' # phases: ',count(mySources); flush(IO_STDOUT)
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
|
||||
|
||||
do ph = 1, phases%length
|
||||
if (mySources(ph)) then
|
||||
phase => phases%get(ph)
|
||||
sources => phase%get('damage')
|
||||
phase => phases%get_dict(ph)
|
||||
sources => phase%get_list('damage')
|
||||
|
||||
associate(prm => param(ph))
|
||||
src => sources%get(1)
|
||||
src => sources%get_dict(1)
|
||||
|
||||
N_cl = src%get_as1dInt('N_cl',defaultVal=emptyIntArray)
|
||||
prm%sum_N_cl = sum(abs(N_cl))
|
||||
|
|
|
@ -34,11 +34,12 @@ module function isobrittle_init() result(mySources)
|
|||
|
||||
logical, dimension(:), allocatable :: mySources
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, &
|
||||
src
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
integer :: Nmembers,ph
|
||||
character(len=pStringLen) :: extmsg = ''
|
||||
|
||||
|
@ -50,18 +51,18 @@ module function isobrittle_init() result(mySources)
|
|||
print'(/,a,i0)', ' # phases: ',count(mySources); flush(IO_STDOUT)
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(state(phases%length))
|
||||
allocate(deltaState(phases%length))
|
||||
|
||||
do ph = 1, phases%length
|
||||
if (mySources(ph)) then
|
||||
phase => phases%get(ph)
|
||||
sources => phase%get('damage')
|
||||
phase => phases%get_dict(ph)
|
||||
sources => phase%get_list('damage')
|
||||
|
||||
associate(prm => param(ph), dlt => deltaState(ph), stt => state(ph))
|
||||
src => sources%get(1)
|
||||
src => sources%get_dict(1)
|
||||
|
||||
prm%W_crit = src%get_asFloat('G_crit')/src%get_asFloat('l_c')
|
||||
|
||||
|
|
|
@ -43,11 +43,11 @@ submodule(phase) mechanical
|
|||
interface
|
||||
|
||||
module subroutine eigen_init(phases)
|
||||
class(tNode), pointer :: phases
|
||||
type(tDict), pointer :: phases
|
||||
end subroutine eigen_init
|
||||
|
||||
module subroutine elastic_init(phases)
|
||||
class(tNode), pointer :: phases
|
||||
type(tDict), pointer :: phases
|
||||
end subroutine elastic_init
|
||||
|
||||
module subroutine plastic_init
|
||||
|
@ -198,7 +198,7 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine mechanical_init(phases)
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases
|
||||
|
||||
integer :: &
|
||||
|
@ -208,7 +208,7 @@ module subroutine mechanical_init(phases)
|
|||
ph, &
|
||||
en, &
|
||||
Nmembers
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
num_crystallite, &
|
||||
phase, &
|
||||
mech
|
||||
|
@ -248,8 +248,8 @@ module subroutine mechanical_init(phases)
|
|||
allocate(phase_mechanical_P(ph)%data(3,3,Nmembers),source=0.0_pReal)
|
||||
allocate(phase_mechanical_S0(ph)%data(3,3,Nmembers),source=0.0_pReal)
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
#if defined(__GFORTRAN__)
|
||||
output_mechanical(ph)%label = output_as1dString(mech)
|
||||
#else
|
||||
|
@ -286,7 +286,7 @@ module subroutine mechanical_init(phases)
|
|||
plasticState(ph)%state0 = plasticState(ph)%state
|
||||
end do
|
||||
|
||||
num_crystallite => config_numerics%get('crystallite',defaultVal=emptyDict)
|
||||
num_crystallite => config_numerics%get_dict('crystallite',defaultVal=emptyDict)
|
||||
|
||||
select case(num_crystallite%get_asString('integrator',defaultVal='FPI'))
|
||||
|
||||
|
|
|
@ -34,15 +34,16 @@ contains
|
|||
|
||||
module subroutine eigen_init(phases)
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases
|
||||
|
||||
integer :: &
|
||||
ph
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phase, &
|
||||
kinematics, &
|
||||
mechanics
|
||||
type(tList), pointer :: &
|
||||
kinematics
|
||||
|
||||
print'(/,1x,a)', '<<<+- phase:mechanical:eigen init -+>>>'
|
||||
|
||||
|
@ -51,9 +52,9 @@ module subroutine eigen_init(phases)
|
|||
allocate(Nmodels(phases%length),source = 0)
|
||||
|
||||
do ph = 1,phases%length
|
||||
phase => phases%get(ph)
|
||||
mechanics => phase%get('mechanical')
|
||||
kinematics => mechanics%get('eigen',defaultVal=emptyList)
|
||||
phase => phases%get_dict(ph)
|
||||
mechanics => phase%get_dict('mechanical')
|
||||
kinematics => mechanics%get_list('eigen',defaultVal=emptyList)
|
||||
Nmodels(ph) = kinematics%length
|
||||
end do
|
||||
|
||||
|
@ -80,27 +81,28 @@ function kinematics_active(kinematics_label,kinematics_length) result(active_ki
|
|||
integer, intent(in) :: kinematics_length !< max. number of kinematics in system
|
||||
logical, dimension(:,:), allocatable :: active_kinematics
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
kinematics, &
|
||||
kinematics_type, &
|
||||
mechanics
|
||||
mechanics, &
|
||||
kinematic
|
||||
type(tList), pointer :: &
|
||||
kinematics
|
||||
integer :: ph,k
|
||||
|
||||
phases => config_material%get('phase')
|
||||
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(active_kinematics(kinematics_length,phases%length), source = .false. )
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
mechanics => phase%get('mechanical')
|
||||
kinematics => mechanics%get('eigen',defaultVal=emptyList)
|
||||
phase => phases%get_dict(ph)
|
||||
mechanics => phase%get_dict('mechanical')
|
||||
kinematics => mechanics%get_list('eigen',defaultVal=emptyList)
|
||||
do k = 1, kinematics%length
|
||||
kinematics_type => kinematics%get(k)
|
||||
active_kinematics(k,ph) = kinematics_type%get_asString('type') == kinematics_label
|
||||
kinematic => kinematics%get_dict(k)
|
||||
active_kinematics(k,ph) = kinematic%get_asString('type') == kinematics_label
|
||||
end do
|
||||
end do
|
||||
|
||||
|
||||
end function kinematics_active
|
||||
|
||||
|
||||
|
@ -113,20 +115,21 @@ function kinematics_active2(kinematics_label) result(active_kinematics)
|
|||
character(len=*), intent(in) :: kinematics_label !< name of kinematic mechanism
|
||||
logical, dimension(:), allocatable :: active_kinematics
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
kinematics, &
|
||||
kinematics_type
|
||||
type(tList), pointer :: &
|
||||
kinematics
|
||||
integer :: ph
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(active_kinematics(phases%length), source = .false.)
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
kinematics => phase%get('damage',defaultVal=emptyList)
|
||||
phase => phases%get_dict(ph)
|
||||
kinematics => phase%get_list('damage',defaultVal=emptyList)
|
||||
if (kinematics%length < 1) return
|
||||
kinematics_type => kinematics%get(1)
|
||||
kinematics_type => kinematics%get_dict(1)
|
||||
if (.not. kinematics_type%contains('type')) continue
|
||||
active_kinematics(ph) = kinematics_type%get_asString('type',defaultVal='n/a') == kinematics_label
|
||||
end do
|
||||
|
|
|
@ -28,12 +28,13 @@ module function thermalexpansion_init(kinematics_length) result(myKinematics)
|
|||
logical, dimension(:,:), allocatable :: myKinematics
|
||||
|
||||
integer :: Ninstances, p, k
|
||||
class(tNode), pointer :: &
|
||||
type(tList), pointer :: &
|
||||
kinematics
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
kinematics, &
|
||||
myConfig
|
||||
mech
|
||||
|
||||
|
||||
print'(/,1x,a)', '<<<+- phase:mechanical:eigen:thermalexpansion init -+>>>'
|
||||
|
||||
|
@ -42,26 +43,23 @@ module function thermalexpansion_init(kinematics_length) result(myKinematics)
|
|||
print'(/,a,i2)', ' # phases: ',Ninstances; flush(IO_STDOUT)
|
||||
if (Ninstances == 0) return
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(Ninstances))
|
||||
allocate(kinematics_thermal_expansion_instance(phases%length), source=0)
|
||||
|
||||
do p = 1, phases%length
|
||||
if (any(myKinematics(:,p))) kinematics_thermal_expansion_instance(p) = count(myKinematics(:,1:p))
|
||||
phase => phases%get(p)
|
||||
phase => phases%get_dict(p)
|
||||
if (count(myKinematics(:,p)) == 0) cycle
|
||||
mech => phase%get('mechanical')
|
||||
kinematics => mech%get('eigen')
|
||||
mech => phase%get_dict('mechanical')
|
||||
kinematics => mech%get_list('eigen')
|
||||
do k = 1, kinematics%length
|
||||
if (myKinematics(k,p)) then
|
||||
associate(prm => param(kinematics_thermal_expansion_instance(p)))
|
||||
|
||||
myConfig => kinematics%get(k)
|
||||
|
||||
prm%A_11 = polynomial(myConfig%asDict(),'A_11','T')
|
||||
prm%A_11 = polynomial(kinematics%get_dict(k),'A_11','T')
|
||||
if (any(phase_lattice(p) == ['hP','tI'])) &
|
||||
prm%A_33 = polynomial(myConfig%asDict(),'A_33','T')
|
||||
|
||||
prm%A_33 = polynomial(kinematics%get_dict(k),'A_33','T')
|
||||
end associate
|
||||
end if
|
||||
end do
|
||||
|
|
|
@ -19,12 +19,12 @@ contains
|
|||
!--------------------------------------------------------------------------------------------------
|
||||
module subroutine elastic_init(phases)
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases
|
||||
|
||||
integer :: &
|
||||
ph
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phase, &
|
||||
mech, &
|
||||
elastic
|
||||
|
@ -38,9 +38,9 @@ module subroutine elastic_init(phases)
|
|||
allocate(param(phases%length))
|
||||
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
elastic => mech%get('elastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
elastic => mech%get_dict('elastic')
|
||||
if (elastic%get_asString('type') /= 'Hooke') call IO_error(200,ext_msg=elastic%get_asString('type'))
|
||||
|
||||
associate(prm => param(ph))
|
||||
|
|
|
@ -421,19 +421,19 @@ function plastic_active(plastic_label) result(active_plastic)
|
|||
character(len=*), intent(in) :: plastic_label !< type of plasticity model
|
||||
logical, dimension(:), allocatable :: active_plastic
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
pl
|
||||
integer :: ph
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(active_plastic(phases%length), source = .false. )
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic',defaultVal = emptyDict)
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic',defaultVal = emptyDict)
|
||||
active_plastic(ph) = pl%get_asString('type',defaultVal='none') == plastic_label
|
||||
end do
|
||||
|
||||
|
|
|
@ -93,7 +93,7 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
|||
a !< non-Schmid coefficients
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -109,7 +109,7 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
|||
print'(/,1x,a)', 'D. Cereceda et al., International Journal of Plasticity 78:242–256, 2016'
|
||||
print'( 1x,a)', 'https://doi.org/10.1016/j.ijplas.2015.09.002'
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(indexDotState(phases%length))
|
||||
allocate(state(phases%length))
|
||||
|
@ -121,9 +121,9 @@ module function plastic_dislotungsten_init() result(myPlasticity)
|
|||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph), &
|
||||
idx_dot => indexDotState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(pl)
|
||||
|
|
|
@ -142,7 +142,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
rho_dip_0 !< initial dipole dislocation density per slip system
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -165,7 +165,7 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
print'( 1x,a)', 'https://doi.org/10.1016/j.actamat.2016.07.032'
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(indexDotState(phases%length))
|
||||
allocate(state(phases%length))
|
||||
|
@ -177,9 +177,9 @@ module function plastic_dislotwin_init() result(myPlasticity)
|
|||
associate(prm => param(ph), stt => state(ph), dst => dependentState(ph), &
|
||||
idx_dot => indexDotState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(pl)
|
||||
|
|
|
@ -56,7 +56,7 @@ module function plastic_isotropic_init() result(myPlasticity)
|
|||
xi_0 !< initial critical stress
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -72,7 +72,7 @@ module function plastic_isotropic_init() result(myPlasticity)
|
|||
print'(/,1x,a)', 'T. Maiti and P. Eisenlohr, Scripta Materialia 145:37–40, 2018'
|
||||
print'( 1x,a)', 'https://doi.org/10.1016/j.scriptamat.2017.09.047'
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(state(phases%length))
|
||||
|
||||
|
@ -81,9 +81,9 @@ module function plastic_isotropic_init() result(myPlasticity)
|
|||
|
||||
associate(prm => param(ph), stt => state(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(pl)
|
||||
|
|
|
@ -79,7 +79,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
|||
a !< non-Schmid coefficients
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -94,7 +94,7 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
|||
print'(/,1x,a)', 'J.A. Wollmershauser et al., International Journal of Fatigue 36:181–193, 2012'
|
||||
print'( 1x,a)', 'https://doi.org/10.1016/j.ijfatigue.2011.07.008'
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(indexDotState(phases%length))
|
||||
allocate(state(phases%length))
|
||||
|
@ -107,9 +107,9 @@ module function plastic_kinehardening_init() result(myPlasticity)
|
|||
associate(prm => param(ph), stt => state(ph), dlt => deltaState(ph), &
|
||||
idx_dot => indexDotState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
#if defined (__GFORTRAN__)
|
||||
prm%output = output_as1dString(pl)
|
||||
|
|
|
@ -17,7 +17,7 @@ module function plastic_none_init() result(myPlasticity)
|
|||
logical, dimension(:), allocatable :: myPlasticity
|
||||
integer :: &
|
||||
ph
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases
|
||||
|
||||
|
||||
|
@ -27,7 +27,7 @@ module function plastic_none_init() result(myPlasticity)
|
|||
print'(/,1x,a)', '<<<+- phase:mechanical:plastic:none init -+>>>'
|
||||
print'(/,a,i0)', ' # phases: ',count(myPlasticity); flush(IO_STDOUT)
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
do ph = 1, phases%length
|
||||
if (.not. myPlasticity(ph)) cycle
|
||||
call phase_allocateState(plasticState(ph),count(material_phaseID == ph),0,0,0)
|
||||
|
|
|
@ -190,7 +190,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
extmsg = ''
|
||||
type(tInitialParameters) :: &
|
||||
ini
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -213,7 +213,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
print'( 1x,a)', 'http://publications.rwth-aachen.de/record/229993'
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
|
||||
allocate(geom(phases%length))
|
||||
|
||||
|
@ -230,9 +230,9 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
associate(prm => param(ph), dot => dotState(ph), stt => state(ph), &
|
||||
st0 => state0(ph), del => deltaState(ph), dst => dependentState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
plasticState(ph)%nonlocal = pl%get_asBool('flux',defaultVal=.True.)
|
||||
#if defined (__GFORTRAN__)
|
||||
|
@ -520,7 +520,7 @@ module function plastic_nonlocal_init() result(myPlasticity)
|
|||
|
||||
if(.not. myPlasticity(ph)) cycle
|
||||
|
||||
phase => phases%get(ph)
|
||||
phase => phases%get_dict(ph)
|
||||
Nmembers = count(material_phaseID == ph)
|
||||
l = 0
|
||||
do t = 1,4
|
||||
|
|
|
@ -92,7 +92,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
a !< non-Schmid coefficients
|
||||
character(len=pStringLen) :: &
|
||||
extmsg = ''
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
mech, &
|
||||
|
@ -106,7 +106,7 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
print'(/,a,i0)', ' # phases: ',count(myPlasticity); flush(IO_STDOUT)
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(indexDotState(phases%length))
|
||||
allocate(state(phases%length))
|
||||
|
@ -117,9 +117,9 @@ module function plastic_phenopowerlaw_init() result(myPlasticity)
|
|||
associate(prm => param(ph), stt => state(ph), &
|
||||
idx_dot => indexDotState(ph))
|
||||
|
||||
phase => phases%get(ph)
|
||||
mech => phase%get('mechanical')
|
||||
pl => mech%get('plastic')
|
||||
phase => phases%get_dict(ph)
|
||||
mech => phase%get_dict('mechanical')
|
||||
pl => mech%get_dict('plastic')
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
! slip related parameters
|
||||
|
|
|
@ -76,11 +76,14 @@ contains
|
|||
!----------------------------------------------------------------------------------------------
|
||||
module subroutine thermal_init(phases)
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases
|
||||
|
||||
class(tNode), pointer :: &
|
||||
phase, thermal, sources
|
||||
type(tDict), pointer :: &
|
||||
phase, &
|
||||
thermal
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
|
||||
integer :: &
|
||||
ph, so, &
|
||||
|
@ -99,8 +102,8 @@ module subroutine thermal_init(phases)
|
|||
Nmembers = count(material_phaseID == ph)
|
||||
allocate(current(ph)%T(Nmembers),source=T_ROOM)
|
||||
allocate(current(ph)%dot_T(Nmembers),source=0.0_pReal)
|
||||
phase => phases%get(ph)
|
||||
thermal => phase%get('thermal',defaultVal=emptyDict)
|
||||
phase => phases%get_dict(ph)
|
||||
thermal => phase%get_dict('thermal',defaultVal=emptyDict)
|
||||
|
||||
! ToDo: temperature dependency of K and C_p
|
||||
if (thermal%length > 0) then
|
||||
|
@ -114,7 +117,7 @@ module subroutine thermal_init(phases)
|
|||
#else
|
||||
param(ph)%output = thermal%get_as1dString('output',defaultVal=emptyStringArray)
|
||||
#endif
|
||||
sources => thermal%get('source',defaultVal=emptyList)
|
||||
sources => thermal%get_list('source',defaultVal=emptyList)
|
||||
thermal_Nsources(ph) = sources%length
|
||||
else
|
||||
thermal_Nsources(ph) = 0
|
||||
|
@ -365,21 +368,23 @@ function thermal_active(source_label,src_length) result(active_source)
|
|||
integer, intent(in) :: src_length !< max. number of sources in system
|
||||
logical, dimension(:,:), allocatable :: active_source
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, thermal, &
|
||||
thermal, &
|
||||
src
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
integer :: p,s
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(active_source(src_length,phases%length), source = .false. )
|
||||
do p = 1, phases%length
|
||||
phase => phases%get(p)
|
||||
thermal => phase%get('thermal',defaultVal=emptyDict)
|
||||
sources => thermal%get('source',defaultVal=emptyList)
|
||||
phase => phases%get_dict(p)
|
||||
thermal => phase%get_dict('thermal',defaultVal=emptyDict)
|
||||
sources => thermal%get_list('source',defaultVal=emptyList)
|
||||
do s = 1, sources%length
|
||||
src => sources%get(s)
|
||||
src => sources%get_dict(s)
|
||||
active_source(s,p) = src%get_asString('type') == source_label
|
||||
end do
|
||||
end do
|
||||
|
|
|
@ -26,11 +26,13 @@ module function dissipation_init(source_length) result(mySources)
|
|||
integer, intent(in) :: source_length
|
||||
logical, dimension(:,:), allocatable :: mySources
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, thermal, &
|
||||
thermal, &
|
||||
src
|
||||
class(tList), pointer :: &
|
||||
sources
|
||||
integer :: so,Nmembers,ph
|
||||
|
||||
|
||||
|
@ -40,18 +42,18 @@ module function dissipation_init(source_length) result(mySources)
|
|||
print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT)
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
phase => phases%get_dict(ph)
|
||||
if (count(mySources(:,ph)) == 0) cycle !ToDo: error if > 1
|
||||
thermal => phase%get('thermal')
|
||||
sources => thermal%get('source')
|
||||
thermal => phase%get_dict('thermal')
|
||||
sources => thermal%get_list('source')
|
||||
do so = 1, sources%length
|
||||
if (mySources(so,ph)) then
|
||||
associate(prm => param(ph))
|
||||
src => sources%get(so)
|
||||
src => sources%get_dict(so)
|
||||
|
||||
prm%kappa = src%get_asFloat('kappa')
|
||||
Nmembers = count(material_phaseID == ph)
|
||||
|
|
|
@ -33,11 +33,13 @@ module function externalheat_init(source_length) result(mySources)
|
|||
integer, intent(in) :: source_length
|
||||
logical, dimension(:,:), allocatable :: mySources
|
||||
|
||||
class(tNode), pointer :: &
|
||||
type(tDict), pointer :: &
|
||||
phases, &
|
||||
phase, &
|
||||
sources, thermal, &
|
||||
thermal, &
|
||||
src
|
||||
type(tList), pointer :: &
|
||||
sources
|
||||
integer :: so,Nmembers,ph
|
||||
|
||||
|
||||
|
@ -47,20 +49,20 @@ module function externalheat_init(source_length) result(mySources)
|
|||
print'(/,a,i2)', ' # phases: ',count(mySources); flush(IO_STDOUT)
|
||||
|
||||
|
||||
phases => config_material%get('phase')
|
||||
phases => config_material%get_dict('phase')
|
||||
allocate(param(phases%length))
|
||||
allocate(source_thermal_externalheat_offset (phases%length), source=0)
|
||||
|
||||
do ph = 1, phases%length
|
||||
phase => phases%get(ph)
|
||||
phase => phases%get_dict(ph)
|
||||
if (count(mySources(:,ph)) == 0) cycle
|
||||
thermal => phase%get('thermal')
|
||||
sources => thermal%get('source')
|
||||
thermal => phase%get_dict('thermal')
|
||||
sources => thermal%get_list('source')
|
||||
do so = 1, sources%length
|
||||
if (mySources(so,ph)) then
|
||||
source_thermal_externalheat_offset(ph) = so
|
||||
associate(prm => param(ph))
|
||||
src => sources%get(so)
|
||||
src => sources%get_dict(so)
|
||||
|
||||
prm%t_n = src%get_as1dFloat('t_n')
|
||||
prm%nIntervals = size(prm%t_n) - 1
|
||||
|
|
|
@ -126,7 +126,7 @@ subroutine selfTest()
|
|||
real(pReal), dimension(5) :: coef
|
||||
integer :: i
|
||||
real(pReal) :: x_ref, x, y
|
||||
class(tNode), pointer :: dict
|
||||
type(tDict), pointer :: dict
|
||||
character(len=pStringLen), dimension(size(coef)) :: coef_s
|
||||
character(len=pStringLen) :: x_ref_s, x_s, YAML_s
|
||||
|
||||
|
@ -156,7 +156,7 @@ subroutine selfTest()
|
|||
'C,T^3: '//trim(adjustl(coef_s(4)))//IO_EOL//&
|
||||
'C,T^4: '//trim(adjustl(coef_s(5)))//IO_EOL//&
|
||||
'T_ref: '//trim(adjustl(x_ref_s))//IO_EOL
|
||||
Dict => YAML_parse_str(trim(YAML_s))
|
||||
dict => YAML_parse_str_asDict(trim(YAML_s))
|
||||
p2 = polynomial(dict%asDict(),'C','T')
|
||||
if (dNeq(p1%at(x),p2%at(x),1.0e-6_pReal)) error stop 'polynomials: init'
|
||||
y = coef(1)+coef(2)*(x-x_ref)+coef(3)*(x-x_ref)**2+coef(4)*(x-x_ref)**3+coef(5)*(x-x_ref)**4
|
||||
|
@ -165,28 +165,28 @@ subroutine selfTest()
|
|||
YAML_s = 'C: 0.0'//IO_EOL//&
|
||||
'C,T: '//trim(adjustl(coef_s(2)))//IO_EOL//&
|
||||
'T_ref: '//trim(adjustl(x_ref_s))//IO_EOL
|
||||
Dict => YAML_parse_str(trim(YAML_s))
|
||||
dict => YAML_parse_str_asDict(trim(YAML_s))
|
||||
p1 = polynomial(dict%asDict(),'C','T')
|
||||
if (dNeq(p1%at(x_ref+x),-p1%at(x_ref-x),1.0e-10_pReal)) error stop 'polynomials: eval(linear)'
|
||||
|
||||
YAML_s = 'C: 0.0'//IO_EOL//&
|
||||
'C,T^2: '//trim(adjustl(coef_s(3)))//IO_EOL//&
|
||||
'T_ref: '//trim(adjustl(x_ref_s))//IO_EOL
|
||||
Dict => YAML_parse_str(trim(YAML_s))
|
||||
dict => YAML_parse_str_asDict(trim(YAML_s))
|
||||
p1 = polynomial(dict%asDict(),'C','T')
|
||||
if (dNeq(p1%at(x_ref+x),p1%at(x_ref-x),1e-10_pReal)) error stop 'polynomials: eval(quadratic)'
|
||||
|
||||
YAML_s = 'Y: '//trim(adjustl(coef_s(1)))//IO_EOL//&
|
||||
'Y,X^3: '//trim(adjustl(coef_s(2)))//IO_EOL//&
|
||||
'X_ref: '//trim(adjustl(x_ref_s))//IO_EOL
|
||||
Dict => YAML_parse_str(trim(YAML_s))
|
||||
dict => YAML_parse_str_asDict(trim(YAML_s))
|
||||
p1 = polynomial(dict%asDict(),'Y','X')
|
||||
if (dNeq(p1%at(x_ref+x)-coef(1),-(p1%at(x_ref-x)-coef(1)),1.0e-8_pReal)) error stop 'polynomials: eval(cubic)'
|
||||
|
||||
YAML_s = 'Y: '//trim(adjustl(coef_s(1)))//IO_EOL//&
|
||||
'Y,X^4: '//trim(adjustl(coef_s(2)))//IO_EOL//&
|
||||
'X_ref: '//trim(adjustl(x_ref_s))//IO_EOL
|
||||
Dict => YAML_parse_str(trim(YAML_s))
|
||||
dict => YAML_parse_str_asDict(trim(YAML_s))
|
||||
p1 = polynomial(dict%asDict(),'Y','X')
|
||||
if (dNeq(p1%at(x_ref+x),p1%at(x_ref-x),1.0e-6_pReal)) error stop 'polynomials: eval(quartic)'
|
||||
|
||||
|
|
Loading…
Reference in New Issue