Newer
Older
program main
!< @brief главная программа
!< @details максимально обобщенный аналог tm.f90 из модели land

Georgiy Faikin
committed
use config, only : config_init, carbon_model_type, environment_data_type, lsm_datafile
use grid, only : grid_init, &
& i0, i1, j0, j1, ntime, ii, jj, tt, nn, mask, date_c, dt, &
& dlon, dlat, dlon_nc, dlat_nc, dt_nc, date_fst, date_lst, ncell_tot, ncell_mask
& environment_calc_at_timestep, &
& environment_calc_at_cell, &
& environment_calc_at_tile

Georgiy Faikin
committed
use carbon, only : carbon_init, &
& carbon_calc_at_timestep, &
& carbon_calc_at_cell, &
& carbon_calc_at_tile, &
& carbon_postprocessing
integer :: progress_pc
integer :: progress_pc_mem = 0
integer, parameter :: cputime_averaging_period = 250
real :: cputime0, cputime1
print('(1x,a,1x,10x,1x,a)'), 'модель углеродного цикла ', trim(carbon_model_type)
print('(1x,a,1x,10x,1x,a)'), 'данные об окружающей среде ', trim(environment_data_type)
if (environment_data_type == 'lsm_offline') then
print('(1x,a,1x,10x,1x,a)'), ' файл ', trim(lsm_datafile)
print('(1x,a,1x,f10.2)'), ' шаг по широте ', dlat_nc
print('(1x,a,1x,f10.2)'), ' шаг по долготе ', dlon_nc
print('(1x,a,1x,i10)'), ' шаг по времени, c ', dt_nc
print*,'---'
print('(1x,a,1x,f10.2)'), 'шаг по широте ', dlat
print('(1x,a,1x,f10.2)'), 'шаг по долготе ', dlon
print('(1x,a,1x,i10)'), 'всего ячеек в области ', ncell_tot
print('(1x,a,1x,i10,1x,"(",i3,"%)")'), ' из них обсчитывается ', ncell_mask, nint(ncell_mask*100./ncell_tot)
print*,'---'
print('(1x,a,1x,10x,a)'), 'стартовая дата ', date_fst%timestamp
print('(1x,a,1x,10x,a)'), 'финальная дата ', date_lst%timestamp
do nn = 1, ntile
if (tile_weight(ii,jj,nn) > 0.) then
call environment_calc_at_tile(ii,jj,nn)
call carbon_calc_at_tile(ii,jj,nn)
endif
enddo
if (tt == cputime_averaging_period) then
call cpu_time(cputime1)
print*
print('(1x,a,4x,f7.2)'), 'примерная прод-ть расчета, мин ', ntime*(cputime1-cputime0)/(60.*cputime_averaging_period)
print*
print*, '----------------------------------------------------------------'
print*
firstcall = .false.
endif
else
progress_pc = floor(tt*100./ntime)
if (progress_pc /= progress_pc_mem) then
print'(1x,a,4x,i3,1x,"%")', date_c%timestamp, progress_pc