Newer
Older
!> @brief main run sfx subroutine
! ----------------------------------------------------------------------------

Evgeny Mortikov
committed
use sfx_data
use sfx_esm, only: &
get_surface_fluxes_vec_esm => get_surface_fluxes_vec, &
numericsType_esm => numericsType
use sfx_log, only: &
get_surface_fluxes_vec_log => get_surface_fluxes_vec, &
numericsType_log => numericsType
use sfx_most, only: &
get_surface_fluxes_vec_most => get_surface_fluxes_vec, &
numericsType_most => numericsType
use sfx_sheba, only: &
get_surface_fluxes_vec_sheba => get_surface_fluxes_vec, &
numericsType_sheba => numericsType
! --------------------------------------------------------------------------------
! directives list
! --------------------------------------------------------------------------------
implicit none
! --------------------------------------------------------------------------------

Evgeny Mortikov
committed
! --------------------------------------------------------------------------------
type(meteoDataVecType) :: meteo !< meteorological data (input)
type(meteoDataType) :: meteo_cell
type(numericsType_esm) :: numerics_esm !< surface flux module (ESM) numerics parameters
type(numericsType_log) :: numerics_log !< surface flux module (LOG) numerics parameters
type(numericsType_most) :: numerics_most !< surface flux module (MOST) numerics parameters
type(numericsType_sheba) :: numerics_sheba !< surface flux module (SHEBA) numerics parameters
! --------------------------------------------------------------------------------
! local variables
! --------------------------------------------------------------------------------
integer :: i
integer :: status
! --------------------------------------------------------------------------------
write(*, *) ' Running SFX model'
write(*, *) ' model = ', trim(get_model_tag(args%model_id))
write(*, *) ' dataset = ', trim(get_dataset_tag(args%dataset_id))
write(*, *) ' filename[IN-COMMON] = ', trim(args%filename_in_common)
write(*, *) ' filename[IN] = ', trim(args%filename_in)
write(*, *) ' filename[OUT] = ', trim(args%filename_out)
!< @brief define number of cells
open(32, file = args%filename_in, iostat = status, status ='old')
write(*, *) ' FAILURE! > unable to open file: ', trim(args%filename_in)
return
end if
num = 0
status = 0
do while (status.eq.0)
read (32, *, iostat = status) meteo_cell%U, meteo_cell%dT, meteo_cell%Tsemi, meteo_cell%dQ
num = num + 1
enddo
num = num - 1
close(32)
! --- print number of elements in dataset
write(*, *) ' size = ', num
if (args%nmax > 0) then
write(*, *) ' nmax = ', args%nmax
num = min(num, args%nmax)
end if
!< @brief allocate input & output data
call allocate_meteo_vec(meteo, num)
call allocate_sfx_vec(sfx, num)
!< @brief read input data common parameters
open(32, file = args%filename_in_common, iostat = status, status = 'old')
write(*, *) ' FAILURE! > unable to open file: ', trim(args%filename_in_common)
return
end if
read(32, *) meteo_cell%h, meteo_cell%z0_m
close(32)
!< @brief read input data
open(32, file = args%filename_in, iostat = status, status = 'old')
write(*, *) ' FAILURE! > unable to open file: ', trim(args%filename_in)
return
end if
do i = 1, num
read(32, *) meteo_cell%U, meteo_cell%dT, meteo_cell%Tsemi, meteo_cell%dQ
meteo%h(i) = meteo_cell%h
meteo%U(i) = meteo_cell%U
meteo%dT(i) = meteo_cell%dT
meteo%Tsemi(i) = meteo_cell%Tsemi
meteo%dQ(i) = meteo_cell%dQ
meteo%z0_m(i) = meteo_cell%z0_m
enddo
close(32)
!< @brief calling flux module
call get_surface_fluxes_vec_esm(sfx, meteo, numerics_esm, num)
call get_surface_fluxes_vec_log(sfx, meteo, numerics_log, num)
call get_surface_fluxes_vec_most(sfx, meteo, numerics_most, num)
call get_surface_fluxes_vec_sheba(sfx, meteo, numerics_sheba, num)
end if
!< @brief write output data
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
sfx%zeta, sfx%Rib, &
sfx%Re, sfx%B, sfx%z0_m, sfx%z0_t, &
sfx%Rib_conv_lim, &
sfx%Cm,sfx%Ct, sfx%Km, sfx%Pr_t_inv, num, '(11(f10.4,3x))', status)
!< @brief deallocate input & output data
call deallocate_meteo_vec(meteo)
call deallocate_sfx_vec(sfx)
end subroutine
program sfx_main
! modules used
! --------------------------------------------------------------------------------
#ifdef USE_CONFIG_PARSER
USE PARSER_SUB_F
USE PARSER
USE sfx_surface
use iso_c_binding, only: C_NULL_CHAR
#endif
use sfx_common
use sfx_config
! --------------------------------------------------------------------------------
! directives list
! --------------------------------------------------------------------------------
implicit none
! --------------------------------------------------------------------------------
! command line arguments
! --------------------------------------------------------------------------------
integer :: num_args
character(len = 128) :: arg

Evgeny Mortikov
committed
character(len = 128), parameter :: arg_key_model = '--model'
character(len = 128), parameter :: arg_key_dataset = '--dataset'
character(len = 128), parameter :: arg_key_output = '--output'
character(len = 128), parameter :: arg_key_nmax = '--nmax'
character(len = 128), parameter :: arg_key_help = '--help'
integer :: is_output_set
! --------------------------------------------------------------------------------
! local variables
! --------------------------------------------------------------------------------
integer :: i
integer :: status
! --------------------------------------------------------------------------------
#ifdef USE_CONFIG_PARSER
character, allocatable :: config_model_name(:)
character, allocatable :: config_dataset_name(:)
character, allocatable :: fn_in_common(:), fn_in(:), fn_out(:)
integer :: sfx_type
real :: z0_m
#endif
!< @brief define default model & dataset
sfx_args%model_id = model_esm !< default = ESM
sfx_args%dataset_id = dataset_mosaic !< default = MOSAiC
sfx_args%nmax = 0
is_output_set = 0
num_args = command_argument_count()
do i = 1, num_args
call get_command_argument(i, arg)
if (trim(arg) == trim(arg_key_help)) then
write(*, *) ' sfx model, usage:'
write(*, *) ' --help '
write(*, *) ' print usage options '

Evgeny Mortikov
committed
write(*, *) ' --model [key]'
write(*, *) ' key = esm (default) || log || most || sheba'
write(*, *) ' --dataset [key]'
write(*, *) ' key = mosaic (default) || irgason || sheba'
write(*, *) ' = lake || papa || toga || user [files]'
write(*, *) ' --output [file]'
write(*, *) ' set output filename '
write(*, *) ' --nmax [value]'
write(*, *) ' max number of data points > 0 '
stop
end if

Evgeny Mortikov
committed
if (trim(arg) == trim(arg_key_model)) then
if (i == num_args) then
write(*, *) ' FAILURE! > missing model [key] argument'
stop
end if

Evgeny Mortikov
committed
call get_command_argument(i + 1, arg)
sfx_args%model_id = get_model_id(arg)
if (sfx_args%model_id == -1) then

Evgeny Mortikov
committed
write(*, *) ' FAILURE! > unknown model [key]: ', trim(arg)
stop
end if
end if
if (trim(arg) == trim(arg_key_dataset)) then
if (i == num_args) then
write(*, *) ' FAILURE! > missing dataset [key] argument'
stop
end if
call get_command_argument(i + 1, arg)
sfx_args%dataset_id = get_dataset_id(arg)
if (sfx_args%dataset_id == -1) then
write(*, *) ' FAILURE! > unknown dataset [key]: ', trim(arg)
stop
end if
write(*, *) ' FAILURE! > incorrect arguments for [user] dataset'
stop
end if
call get_command_argument(i + 2, sfx_args%filename_in_common)
call get_command_argument(i + 3, sfx_args%filename_in)
end if
end if
if (trim(arg) == trim(arg_key_output)) then
if (i == num_args) then
write(*, *) ' FAILURE! > missing output [key] argument'
call get_command_argument(i + 1, sfx_args%filename_out)
end if
if (trim(arg) == trim(arg_key_nmax)) then
if (i == num_args) then
write(*, *) ' FAILURE! > missing nmax [key] argument'
stop
end if
call get_command_argument(i + 1, arg)
if (status /= 0) then
write(*, *) ' FAILURE! > expecting int nmax [value]'
stop
end if
write(*, *) ' FAILURE! > nmax [value] should be positive'
stop
end if
end if
end do
!< @brief set input (& output) filenames for specific dataset
if (sfx_args%dataset_id /= dataset_user) then
sfx_args%filename_in_common = get_dataset_param_filename(sfx_args%dataset_id)
sfx_args%filename_in = get_dataset_filename(sfx_args%dataset_id)
end if
if (is_output_set == 0) then
sfx_args%filename_out = 'output-' // trim(get_dataset_tag(sfx_args%dataset_id)) // '.txt'
end if
#ifdef USE_CONFIG_PARSER
call run("config.txt"//C_NULL_CHAR)
call get_charf("model.type"//C_NULL_CHAR, config_model_name)
if (compare_char_arrays(config_model_name, trim(model_esm_tag))) then
else if (compare_char_arrays(config_model_name, trim(model_log_tag))) then
else if (compare_char_arrays(config_model_name, trim(model_most_tag))) then
else if (compare_char_arrays(config_model_name, trim(model_sheba_tag))) then
model_id = model_sheba
else
write(*, *) ' FAILURE! > unknown model [key]: ', config_model_name
stop
end if
call get_charf("dataset.type"//C_NULL_CHAR, config_dataset_name)
if (compare_char_arrays(config_dataset_name, trim(dataset_mosaic_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_irgason_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_sheba_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_lake_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_papa_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_toga_tag))) then
else if (compare_char_arrays(config_dataset_name, trim(dataset_user_tag))) then
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
dataset_id = dataset_USER
!call get_charf("dataset.filename"//C_NULL_CHAR, config_dataset_filename)
!call get_charf("dataset.filename_params"//C_NULL_CHAR, config_dataset_filename_params)
write(*, *) ' FAILURE! > user dataset is not supported: ', config_dataset_name
stop
!call get_command_argument(i + 2, filename_in_common)
!call get_command_argument(i + 3, filename_in)
!call get_command_argument(i + 4, filename_out)
else
write(*, *) ' FAILURE! > unknown dataset [key]: ', config_dataset_name
stop
end if
!call get_charf("input_files.filename_in_common"//C_NULL_CHAR, fn_in_common)
!call get_charf("input_files.filename_in"//C_NULL_CHAR, fn_in)
!if (is_output_set == 0) call get_charf("input_files.filename_out"//C_NULL_CHAR, fn_out)
!sfx_type = get_sfx_type("surface.surface_type"//C_NULL_CHAR)
!if ( (sfx_type == surface_ocean) .or. (sfx_type == surface_lake) ) then
! call get_float("surface.z0_m"//C_NULL_CHAR, z0_m)
!end if
!write(*, *) "fn_in_common: ", fn_in_common
!write(*, *) "fn_in: ", fn_in
!if (is_output_set == 0) write(*, *) "fn_out: ", fn_out
!write(*, *) "sfx_type: ", sfx_type
!if ( (sfx_type == surface_ocean) .or. (sfx_type == surface_lake) ) then
! write(*, *) "z0_m: ", z0_m
!end if
!call get_float("dataset.h"//C_NULL_CHAR, meteo_cell%h)
!call get_float("dataset.z0_m"//C_NULL_CHAR, meteo_cell%z0_m)
deallocate(config_model_name)
deallocate(config_dataset_name)
!deallocate( fn_in_common )
!deallocate( fn_in )
!if (is_output_set == 0) deallocate( fn_out )
!< @brief running main driver
call run(sfx_args)