DAMASK_EICMD/src/config.f90

124 lines
4.0 KiB
Fortran
Raw Normal View History

2020-01-27 00:26:30 +05:30
!--------------------------------------------------------------------------------------------------
2018-06-10 14:37:17 +05:30
!> @author Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
2020-08-15 19:32:10 +05:30
!> @brief Reads in the material, numerics & debug configuration from their respective file
!> @details Reads the material configuration file, where solverJobName.yaml takes
!! precedence over material.yaml.
2018-06-10 14:37:17 +05:30
!--------------------------------------------------------------------------------------------------
module config
2019-05-15 02:42:32 +05:30
use prec
use DAMASK_interface
use IO
2020-06-16 22:17:19 +05:30
use YAML_parse
use YAML_types
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
#ifdef PETSc
#include <petsc/finclude/petscsys.h>
use petscsys
#endif
2019-03-29 13:04:44 +05:30
implicit none
2019-05-15 02:42:32 +05:30
private
2020-08-15 19:32:10 +05:30
class(tNode), pointer, public :: &
material_root, &
numerics_root, &
debug_root
integer, protected, public :: &
worldrank = 0, & !< MPI worldrank (/=0 for MPI simulations only)
worldsize = 1 !< MPI worldsize (/=1 for MPI simulations only)
2019-03-29 13:04:44 +05:30
public :: &
config_init, &
config_deallocate
contains
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
!> @brief calls subroutines that reads material, numerics and debug configuration files
!--------------------------------------------------------------------------------------------------
subroutine config_init
2020-08-15 19:32:10 +05:30
write(6,'(/,a)') ' <<<+- config init -+>>>'; flush(6)
call parse_material
call parse_numerics
call parse_debug
end subroutine config_init
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief reads material.yaml
!--------------------------------------------------------------------------------------------------
subroutine parse_material
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
logical :: fileExists
2020-09-12 19:26:59 +05:30
character(len=:), allocatable :: fname
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
fname = getSolverJobName()//'.yaml'
inquire(file=fname,exist=fileExists)
if(.not. fileExists) then
fname = 'material.yaml'
inquire(file=fname,exist=fileExists)
if(.not. fileExists) call IO_error(100,ext_msg=fname)
2019-03-29 13:04:44 +05:30
endif
2020-09-12 19:26:59 +05:30
write(6,*) 'reading '//fname; flush(6)
material_root => parse_flow(to_flow(IO_read(fname)))
2018-06-09 17:18:37 +05:30
2020-08-15 19:32:10 +05:30
end subroutine parse_material
2019-03-13 02:18:33 +05:30
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
!> @brief reads in parameters from numerics.yaml and sets openMP related parameters. Also does
! a sanity check
2019-03-13 02:18:33 +05:30
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
subroutine parse_numerics
logical :: fexist
2020-09-12 19:26:59 +05:30
integer :: ierr
2020-08-15 19:32:10 +05:30
#ifdef PETSc
call MPI_Comm_rank(PETSC_COMM_WORLD,worldrank,ierr);CHKERRQ(ierr)
call MPI_Comm_size(PETSC_COMM_WORLD,worldsize,ierr);CHKERRQ(ierr)
#endif
numerics_root => emptyDict
inquire(file='numerics.yaml', exist=fexist)
if (fexist) then
2020-09-12 19:26:59 +05:30
write(6,*) 'reading numerics.yaml'; flush(6)
numerics_root => parse_flow(to_flow(IO_read('numerics.yaml')))
2019-03-13 02:18:33 +05:30
endif
2020-08-15 19:32:10 +05:30
end subroutine parse_numerics
2019-03-13 02:18:33 +05:30
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
!> @brief reads in parameters from debug.yaml
!--------------------------------------------------------------------------------------------------
2020-08-15 19:32:10 +05:30
subroutine parse_debug
2020-08-15 19:32:10 +05:30
logical :: fexist
2020-08-15 19:32:10 +05:30
debug_root => emptyDict
inquire(file='debug.yaml', exist=fexist)
fileExists: if (fexist) then
2020-09-12 19:26:59 +05:30
write(6,*) 'reading debug.yaml'; flush(6)
debug_root => parse_flow(to_flow(IO_read('debug.yaml')))
2020-08-15 19:32:10 +05:30
endif fileExists
2020-08-15 19:32:10 +05:30
end subroutine parse_debug
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
!> @brief deallocates material.yaml structure
!--------------------------------------------------------------------------------------------------
subroutine config_deallocate
2020-09-12 19:26:59 +05:30
deallocate(material_root) !ToDo: deallocation of numerics debug (optional)
end subroutine config_deallocate
end module config