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
|
2023-02-05 19:28:24 +05:30
|
|
|
!> @brief Read in the material and numerics configuration from their respective file.
|
2018-06-10 14:37:17 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2018-06-14 10:09:49 +05:30
|
|
|
module config
|
2019-05-17 02:26:48 +05:30
|
|
|
use IO
|
2023-03-01 01:27:44 +05:30
|
|
|
use misc
|
2020-06-16 22:17:19 +05:30
|
|
|
use YAML_parse
|
|
|
|
use YAML_types
|
2023-01-19 22:07:45 +05:30
|
|
|
use result
|
2021-07-27 10:58:35 +05:30
|
|
|
use parallelization
|
2023-06-07 19:25:01 +05:30
|
|
|
#if defined(MESH) || defined(GRID)
|
|
|
|
use CLI
|
|
|
|
#endif
|
2022-06-22 02:16:54 +05:30
|
|
|
implicit none(type,external)
|
2019-05-15 02:42:32 +05:30
|
|
|
private
|
2019-05-17 02:26:48 +05:30
|
|
|
|
2022-10-25 21:39:36 +05:30
|
|
|
type(tDict), pointer, public :: &
|
2020-09-13 14:09:17 +05:30
|
|
|
config_material, &
|
2023-02-05 19:28:24 +05:30
|
|
|
config_numerics
|
2020-08-15 19:32:10 +05:30
|
|
|
|
2019-03-29 13:04:44 +05:30
|
|
|
public :: &
|
|
|
|
config_init, &
|
2023-02-28 12:25:34 +05:30
|
|
|
config_material_deallocate, &
|
|
|
|
config_numerics_deallocate, &
|
2023-03-01 01:27:44 +05:30
|
|
|
config_listReferences
|
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
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-02-05 19:28:24 +05:30
|
|
|
!> @brief Read *.yaml configuration files.
|
2018-06-27 00:00:41 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2022-04-24 08:13:44 +05:30
|
|
|
subroutine config_init()
|
2019-05-17 02:26:48 +05:30
|
|
|
|
2021-11-15 23:05:44 +05:30
|
|
|
print'(/,1x,a)', '<<<+- config init -+>>>'; flush(IO_STDOUT)
|
2021-07-27 10:58:35 +05:30
|
|
|
|
2023-07-10 23:35:17 +05:30
|
|
|
#if defined(MESH) || defined(GRID)
|
|
|
|
config_material => parse(CLI_materialFile,'material configuration')
|
|
|
|
#else
|
|
|
|
config_material => parse('material.yaml','material configuration')
|
|
|
|
#endif
|
|
|
|
|
|
|
|
config_numerics => emptyDict
|
|
|
|
#if defined(MESH) || defined(GRID)
|
|
|
|
if (allocated(CLI_numericsFile)) &
|
|
|
|
config_numerics => parse(CLI_numericsFile,'numerics configuration')
|
|
|
|
#else
|
|
|
|
MSCMarc: block
|
|
|
|
logical :: exists
|
|
|
|
inquire(file='numerics.yaml',exist=exists)
|
|
|
|
if (exists) config_numerics => parse('numerics.yaml','numerics configuration')
|
|
|
|
end block MSCMarc
|
|
|
|
#endif
|
2020-08-15 19:32:10 +05:30
|
|
|
|
|
|
|
end subroutine config_init
|
|
|
|
|
2019-03-29 13:04:44 +05:30
|
|
|
|
2023-02-28 12:25:34 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Deallocate config_material.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine config_material_deallocate()
|
|
|
|
|
|
|
|
print'(/,1x,a)', 'deallocating material configuration'; flush(IO_STDOUT)
|
|
|
|
deallocate(config_material)
|
|
|
|
|
|
|
|
end subroutine config_material_deallocate
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Deallocate config_numerics if present.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
subroutine config_numerics_deallocate()
|
|
|
|
|
|
|
|
if (.not. associated(config_numerics, emptyDict)) then
|
|
|
|
print'(/,1x,a)', 'deallocating numerics configuration'; flush(IO_STDOUT)
|
|
|
|
deallocate(config_numerics)
|
|
|
|
end if
|
|
|
|
|
|
|
|
end subroutine config_numerics_deallocate
|
|
|
|
|
|
|
|
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
|
|
|
!> @brief Return string with references from dict.
|
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-03-01 01:27:44 +05:30
|
|
|
function config_listReferences(config,indent) result(references)
|
2023-02-28 12:25:34 +05:30
|
|
|
|
2023-07-09 16:55:37 +05:30
|
|
|
type(tDict), intent(in) :: config
|
|
|
|
integer, intent(in), optional :: indent
|
2023-02-28 12:25:34 +05:30
|
|
|
character(len=:), allocatable :: references
|
|
|
|
|
|
|
|
type(tList), pointer :: ref
|
2023-03-01 01:27:44 +05:30
|
|
|
character(len=:), allocatable :: filler
|
2023-02-28 12:25:34 +05:30
|
|
|
integer :: r
|
|
|
|
|
|
|
|
|
2023-03-01 01:27:44 +05:30
|
|
|
filler = repeat(' ',misc_optional(indent,0))
|
2023-02-28 12:25:34 +05:30
|
|
|
ref => config%get_list('references',emptyList)
|
2023-03-01 01:27:44 +05:30
|
|
|
if (ref%length == 0) then
|
|
|
|
references = ''
|
|
|
|
else
|
2023-02-28 12:25:34 +05:30
|
|
|
references = 'references:'
|
|
|
|
do r = 1, ref%length
|
2023-06-04 10:47:38 +05:30
|
|
|
references = references//IO_EOL//filler//'- '//IO_wrapLines(ref%get_asStr(r),filler=filler//' ')
|
2023-02-28 12:25:34 +05:30
|
|
|
end do
|
|
|
|
end if
|
|
|
|
|
2023-03-01 01:27:44 +05:30
|
|
|
end function config_listReferences
|
2023-02-28 12:25:34 +05:30
|
|
|
|
|
|
|
|
2020-08-15 19:32:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-10 23:35:17 +05:30
|
|
|
!> @brief Read configuration, spread over all processes, and add to DADF5.
|
2020-08-15 19:32:10 +05:30
|
|
|
!--------------------------------------------------------------------------------------------------
|
2023-07-10 23:35:17 +05:30
|
|
|
function parse(fname,description)
|
2019-03-29 13:04:44 +05:30
|
|
|
|
2023-07-10 23:35:17 +05:30
|
|
|
character(len=*), intent(in) :: fname, description
|
|
|
|
type(tDict), pointer :: parse
|
|
|
|
|
|
|
|
character(len=:), allocatable :: fileContent
|
2021-07-27 12:05:52 +05:30
|
|
|
|
2023-07-09 16:55:37 +05:30
|
|
|
|
2021-07-27 10:58:35 +05:30
|
|
|
if (worldrank == 0) then
|
2023-07-10 23:35:17 +05:30
|
|
|
print'(/,1x,a)', 'reading '//description; flush(IO_STDOUT)
|
2023-06-23 03:36:44 +05:30
|
|
|
fileContent = IO_read(fname)
|
2023-01-19 22:07:45 +05:30
|
|
|
call result_openJobFile(parallel=.false.)
|
2023-07-12 00:07:21 +05:30
|
|
|
call result_addSetupFile(fileContent,fname,description)
|
2023-02-21 20:48:17 +05:30
|
|
|
call result_closeJobFile()
|
2021-11-15 23:05:44 +05:30
|
|
|
end if
|
2021-07-27 12:24:17 +05:30
|
|
|
call parallelization_bcast_str(fileContent)
|
2021-07-27 12:05:52 +05:30
|
|
|
|
2023-07-10 23:35:17 +05:30
|
|
|
parse => YAML_parse_str_asDict(fileContent)
|
2019-03-13 02:18:33 +05:30
|
|
|
|
2023-07-10 23:35:17 +05:30
|
|
|
end function parse
|
2019-03-13 02:18:33 +05:30
|
|
|
|
2018-06-14 10:09:49 +05:30
|
|
|
end module config
|