Skip to content
Snippets Groups Projects
main.f90 4.57 KiB
Newer Older
  • Learn to ignore specific revisions
  • program main
    
        !< @brief главная программа
        !< @details максимально обобщенный аналог tm.f90 из модели land
    
    
        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
    
    a_medvedev's avatar
    a_medvedev committed
        use environment, only : environment_init, &
    
    a_medvedev's avatar
    a_medvedev committed
                              & environment_calc_at_timestep, &
                              & environment_calc_at_cell, &
                              & environment_calc_at_tile
    
        use carbon,      only : carbon_init, &
                              & carbon_calc_at_timestep, &
                              & carbon_calc_at_cell, &
                              & carbon_calc_at_tile, &
                              & carbon_postprocessing
    
        use carbon_core, only : ntile, tile_weight
    
        integer :: progress_pc
        integer :: progress_pc_mem = 0
    
        integer, parameter :: cputime_averaging_period = 250
        real :: cputime0, cputime1
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        logical :: firstcall = .true.
    
        call config_init()
    
        call grid_init()
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        print('(1x,a,1x,10x,1x,a)'),           'модель углеродного цикла       ', trim(carbon_model_type)
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        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
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        print*,'---'
        print('(1x,a,1x,f10.2)'),              'шаг по широте                  ', dlat
        print('(1x,a,1x,f10.2)'),              'шаг по долготе                 ', dlon
    
        print('(1x,a,1x,i10)'),                'всего ячеек в области          ', ncell_tot
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        print('(1x,a,1x,i10,1x,"(",i3,"%)")'), '    из них обсчитывается       ', ncell_mask, nint(ncell_mask*100./ncell_tot)
        print*,'---'
    
        print('(1x,a,1x,i10)'),                'шаг по времени, с              ', dt
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        print('(1x,a,1x,i10)'),                'число шагов по времени         ', ntime
    
        print('(1x,a,1x,10x,a)'),              'стартовая дата                 ', date_fst%timestamp
        print('(1x,a,1x,10x,a)'),              'финальная дата                 ', date_lst%timestamp
    
        call environment_init()
    
        call cpu_time(cputime0)
    
    a_medvedev's avatar
    +  
    a_medvedev committed
        
    
        do tt = 1, ntime
    
    a_medvedev's avatar
    a_medvedev committed
            
    
    a_medvedev's avatar
    a_medvedev committed
            call environment_calc_at_timestep()
    
            call carbon_calc_at_timestep()
    
            
            do jj = j0, j1
                do ii = i0, i1
    
    a_medvedev's avatar
    +  
    a_medvedev committed
                    if (mask(ii,jj) == 1) then
    
    a_medvedev's avatar
    a_medvedev committed
                        call environment_calc_at_cell(ii,jj)
                        
    
                        call carbon_calc_at_cell(ii,jj)
    
                        do nn = 1, ntile
                            if (tile_weight(ii,jj,nn) > 0.) then
    
    a_medvedev's avatar
    a_medvedev committed
                            
                                call environment_calc_at_tile(ii,jj,nn)
                                
                                call carbon_calc_at_tile(ii,jj,nn)
                                
                            endif
                        enddo
    
            call date_c%shift(dt)
    
    a_medvedev's avatar
    +  
    a_medvedev committed
            if (firstcall) then
    
                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
    
    a_medvedev's avatar
    +  
    a_medvedev committed
            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
    
    a_medvedev's avatar
    +  
    a_medvedev committed
                    progress_pc_mem = progress_pc
                endif
            endif