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
|
2020-09-13 13:49:38 +05:30
|
|
|
!! precedence over material.yaml.
|
2018-06-10 14:37:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-06-14 10:09:49 +05:30
|
|
|
module config
|
2019-05-15 02:42:32 +05:30
|
|
|
use prec
|
2019-05-17 02:26:48 +05:30
|
|
|
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
|
2019-05-17 02:26:48 +05:30
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
class(tNode), pointer, public :: &
|
2020-09-13 14:09:17 +05:30
|
|
|
config_material, &
|
|
|
|
config_numerics, &
|
|
|
|
config_debug
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2019-03-29 13:04:44 +05:30
|
|
|
public :: &
|
|
|
|
config_init, &
|
|
|
|
config_deallocate
|
2018-06-10 22:08:31 +05:30
|
|
|
|
2018-06-09 00:31:58 +05:30
|
|
|
contains
|
|
|
|
|
2018-06-27 00:00:41 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-08-15 19:32:10 +05:30
|
|
|
!> @brief calls subroutines that reads material, numerics and debug configuration files
|
2018-06-27 00:00:41 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2019-03-13 02:57:45 +05:30
|
|
|
subroutine config_init
|
2019-05-17 02:26:48 +05:30
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
write(6,'(/,a)') ' <<<+- config init -+>>>'; flush(6)
|
2020-09-13 13:49:38 +05:30
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
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)
|
2020-09-13 14:09:17 +05:30
|
|
|
config_material => 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-13 14:09:17 +05:30
|
|
|
config_numerics => emptyDict
|
2020-08-15 19:32:10 +05:30
|
|
|
inquire(file='numerics.yaml', exist=fexist)
|
|
|
|
if (fexist) then
|
2020-09-12 19:26:59 +05:30
|
|
|
write(6,*) 'reading numerics.yaml'; flush(6)
|
2020-09-13 14:09:17 +05:30
|
|
|
config_numerics => 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
|
|
|
|
2018-06-09 00:31:58 +05:30
|
|
|
|
2018-08-04 23:09:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-08-15 19:32:10 +05:30
|
|
|
!> @brief reads in parameters from debug.yaml
|
2018-08-04 23:09:50 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2020-08-15 19:32:10 +05:30
|
|
|
subroutine parse_debug
|
2018-06-27 00:00:41 +05:30
|
|
|
|
2020-09-13 13:49:38 +05:30
|
|
|
logical :: fexist
|
2018-08-21 11:44:59 +05:30
|
|
|
|
2020-09-13 14:09:17 +05:30
|
|
|
config_debug => emptyDict
|
2020-08-15 19:32:10 +05:30
|
|
|
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)
|
2020-09-13 14:09:17 +05:30
|
|
|
config_debug => parse_flow(to_flow(IO_read('debug.yaml')))
|
2020-08-15 19:32:10 +05:30
|
|
|
endif fileExists
|
2018-08-21 11:44:59 +05:30
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
end subroutine parse_debug
|
2018-08-21 11:44:59 +05:30
|
|
|
|
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief deallocates material.yaml structure
|
2020-09-13 13:49:38 +05:30
|
|
|
!ToDo: deallocation of numerics debug (optional)
|
2020-08-15 19:32:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine config_deallocate
|
2018-06-27 00:00:41 +05:30
|
|
|
|
2020-09-13 14:09:17 +05:30
|
|
|
deallocate(config_material)
|
2020-09-12 19:26:59 +05:30
|
|
|
|
2018-06-27 00:00:41 +05:30
|
|
|
end subroutine config_deallocate
|
|
|
|
|
2018-06-14 10:09:49 +05:30
|
|
|
end module config
|