! Created by Andrey Debolskiy on 18.10.2024. module config_utils use config_parser use ISO_C_BINDING, only: C_NULL_CHAR use parkinds, only: rf=>kind_rf, im=>kind_im implicit none integer, public, save:: is_config_initialized = 0 public init_config, get_fluid_params, get_grid_params !public get_geo_forcing, get_heat_forcing contains subroutine init_config(fname,status, ierr) implicit none character(len = *), intent(in) ::fname integer,intent(out):: status, ierr call c_config_run(trim(fname)//C_NULL_CHAR, status) if (status == 0) then write(*, *) ' FAILURE! > unable to parse configuration file: ', trim(fname) return end if is_config_initialized = 1 end subroutine init_config subroutine get_fluid_params(fluid_params, status, ierr) use phys_fluid, only: fluidParamsDataType type(fluidParamsDataType), intent(inout):: fluid_params integer,intent(out):: status, ierr ierr = 0 if( is_config_initialized /= 0 ) then ! Fluid params call c_config_is_varname("fluid.tref"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_float("fluid.tref"//C_NULL_CHAR, fluid_params%tref, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("fluid.pref"//C_NULL_CHAR, status) if ((status /= 0)) then !< mandatory in user dataset call c_config_get_float("fluid.pref"//C_NULL_CHAR, fluid_params%pref, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("fluid.beta"//C_NULL_CHAR, status) if ((status /= 0)) then !< mandatory in user dataset call c_config_get_float("fluid.beta"//C_NULL_CHAR, fluid_params%beta, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("fluid.g"//C_NULL_CHAR, status) if ((status /= 0)) then !< mandatory in user dataset call c_config_get_float("fluid.g"//C_NULL_CHAR, fluid_params%g, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("fluid.kappa"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_float("fluid.kappa"//C_NULL_CHAR, fluid_params%kappa, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if end if end subroutine get_fluid_params subroutine get_grid_params(grid, status, ierr) use pbl_grid, only: pblgridDataType, & grid_inmcm21_tag, grid_inmcm73_tag, & grid_streached_tag, grid_uniform_tag, & set_pbl_grid_uniform implicit none type(pblgridDataType), intent(inout):: grid integer,intent(out):: status, ierr character(len=50) :: tag character, allocatable :: config_field(:) real(kind=rf):: h_bot, h_top integer(kind=im):: nz ierr = 0 if( is_config_initialized /= 0 ) then ! grid type call c_config_is_varname("grid.type"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_string("grid.type"//C_NULL_CHAR, config_field, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if if (trim(tag) == trim(grid_uniform_tag)) then call c_config_is_varname("grid.nz"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_int("grid.nz"//C_NULL_CHAR, nz, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("grid.h_bot"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_float("grid.h_bot"//C_NULL_CHAR, h_bot, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call c_config_is_varname("grid.h_top"//C_NULL_CHAR, status) if ((status /= 0)) then call c_config_get_float("grid.h_top"//C_NULL_CHAR, h_top, status) if (status == 0) then ierr = 1 ! signal ERROR return end if end if call set_pbl_grid_uniform(grid, h_bot, h_top, nz) end if else status = 0 ierr = 2 end if end subroutine get_grid_params !> @brief character array to string conversion function char_array2str(char_array) result(str) ! ---------------------------------------------------------------------------- implicit none character, intent(in) :: char_array(:) character(len=:), allocatable :: str integer :: i ! ---------------------------------------------------------------------------- str = "" do i = 1, size(char_array) str = str(:) // char_array(i) end do end function end module config_utils