DAMASK_EICMD/src/config.f90

141 lines
4.2 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
2022-04-26 21:49:13 +05:30
!> @brief Read in the configuration of material, numerics, and debug from their respective file
2018-06-10 14:37:17 +05:30
!--------------------------------------------------------------------------------------------------
module config
use IO
2020-06-16 22:17:19 +05:30
use YAML_parse
use YAML_types
2023-01-19 22:07:45 +05:30
use result
use parallelization
2020-08-15 19:32:10 +05:30
implicit none(type,external)
2019-05-15 02:42:32 +05:30
private
type(tDict), pointer, public :: &
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
contains
!--------------------------------------------------------------------------------------------------
2020-09-14 00:58:53 +05:30
!> @brief Real *.yaml configuration files.
!--------------------------------------------------------------------------------------------------
2022-04-24 08:13:44 +05:30
subroutine config_init()
print'(/,1x,a)', '<<<+- config init -+>>>'; flush(IO_STDOUT)
2022-04-24 08:13:44 +05:30
call parse_material()
call parse_numerics()
call parse_debug()
2020-08-15 19:32:10 +05:30
end subroutine config_init
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
2022-04-24 08:13:44 +05:30
!> @brief Read material.yaml.
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
subroutine parse_material()
2019-03-29 13:04:44 +05:30
2020-08-15 19:32:10 +05:30
logical :: fileExists
character(len=:), allocatable :: fileContent
2021-02-13 04:05:06 +05:30
inquire(file='material.yaml',exist=fileExists)
if (.not. fileExists) call IO_error(100,ext_msg='material.yaml')
2021-07-27 12:05:52 +05:30
if (worldrank == 0) then
print'(/,1x,a)', 'reading material.yaml'; flush(IO_STDOUT)
2021-07-27 12:24:17 +05:30
fileContent = IO_read('material.yaml')
2023-01-19 22:07:45 +05:30
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup','material.yaml','main configuration')
call result_closeJobFile
end if
2021-07-27 12:24:17 +05:30
call parallelization_bcast_str(fileContent)
2021-07-27 12:05:52 +05:30
config_material => YAML_parse_str_asDict(fileContent)
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-09-14 00:58:53 +05:30
!> @brief Read numerics.yaml.
2019-03-13 02:18:33 +05:30
!--------------------------------------------------------------------------------------------------
subroutine parse_numerics()
2020-08-15 19:32:10 +05:30
logical :: fileExists
character(len=:), allocatable :: fileContent
2020-08-15 19:32:10 +05:30
2021-02-13 04:05:06 +05:30
config_numerics => emptyDict
2021-07-27 12:05:52 +05:30
inquire(file='numerics.yaml', exist=fileExists)
if (fileExists) then
2021-07-27 12:05:52 +05:30
if (worldrank == 0) then
print'(1x,a)', 'reading numerics.yaml'; flush(IO_STDOUT)
2021-07-27 12:24:17 +05:30
fileContent = IO_read('numerics.yaml')
if (len(fileContent) > 0) then
2023-01-19 22:07:45 +05:30
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup','numerics.yaml','numerics configuration')
call result_closeJobFile
end if
end if
2021-07-27 12:24:17 +05:30
call parallelization_bcast_str(fileContent)
2021-07-27 12:05:52 +05:30
config_numerics => YAML_parse_str_asDict(fileContent)
2021-07-27 12:05:52 +05:30
end if
2019-03-13 02:18:33 +05:30
2020-08-15 19:32:10 +05:30
end subroutine parse_numerics
2019-03-13 02:18:33 +05:30
!--------------------------------------------------------------------------------------------------
2020-09-14 00:58:53 +05:30
!> @brief Read debug.yaml.
!--------------------------------------------------------------------------------------------------
subroutine parse_debug()
logical :: fileExists
character(len=:), allocatable :: fileContent
2021-02-13 04:05:06 +05:30
config_debug => emptyDict
2021-07-27 12:05:52 +05:30
inquire(file='debug.yaml', exist=fileExists)
if (fileExists) then
2021-07-27 12:05:52 +05:30
if (worldrank == 0) then
print'(1x,a)', 'reading debug.yaml'; flush(IO_STDOUT)
2021-07-27 12:24:17 +05:30
fileContent = IO_read('debug.yaml')
if (len(fileContent) > 0) then
2023-01-19 22:07:45 +05:30
call result_openJobFile(parallel=.false.)
call result_writeDataset_str(fileContent,'setup','debug.yaml','debug configuration')
call result_closeJobFile
end if
end if
2021-07-27 12:24:17 +05:30
call parallelization_bcast_str(fileContent)
2021-07-27 12:05:52 +05:30
config_debug => YAML_parse_str_asDict(fileContent)
2021-07-27 12:05:52 +05:30
end if
2020-08-15 19:32:10 +05:30
end subroutine parse_debug
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
2020-09-14 00:58:53 +05:30
!> @brief Deallocate config_material.
2021-05-23 03:40:46 +05:30
!ToDo: deallocation of numerics and debug (optional)
2020-08-15 19:32:10 +05:30
!--------------------------------------------------------------------------------------------------
subroutine config_deallocate
deallocate(config_material)
2020-09-12 19:26:59 +05:30
end subroutine config_deallocate
end module config