Ignore:
Timestamp:
Feb 22, 2016 3:49:32 PM (8 years ago)
Author:
maronga
Message:

some changes in land surface model, radiation model, nudging and some minor updates

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/land_surface_model.f90

    r1710 r1757  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Bugfix: set tm_soil_m to zero after allocation. Added parameter
     22! unscheduled_radiation_calls to control calls of the radiation model based on
     23! the skin temperature change during one time step (preliminary version). Set
     24! qsws_soil_eb to zero at model start (previously set to qsws_eb). Removed MAX
     25! function as it cannot be vectorized.
    2226!
    2327! Former revisions:
     
    132136    USE radiation_model_mod,                                                   &
    133137        ONLY:  force_radiation_call, radiation_scheme, rad_net, rad_sw_in,     &
    134                rad_lw_out, rad_lw_out_change_0, sigma_sb
     138               rad_lw_out, rad_lw_out_change_0, sigma_sb,                      &
     139               unscheduled_radiation_calls
    135140       
    136141#if defined ( __rrtmg )
     
    320325
    321326    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::                                 &
    322               tt_soil_m, & !< t_soil storage array 
    323               tm_soil_m, & !< m_soil storage array 
     327              tt_soil_m, & !< t_soil storage array
     328              tm_soil_m, & !< m_soil storage array
    324329              root_fr      !< root fraction (sum=1)
    325330
     
    668673       tt_surface_m = 0.0_wp
    669674       tt_soil_m    = 0.0_wp
     675       tm_soil_m    = 0.0_wp
    670676       tm_liq_eb_m  = 0.0_wp
    671677       c_liq        = 0.0_wp
     
    681687
    682688       qsws_liq_eb  = 0.0_wp
    683        qsws_soil_eb = qsws_eb
     689       qsws_soil_eb = 0.0_wp
    684690       qsws_veg_eb  = 0.0_wp
    685691
     
    12351241
    12361242!
    1237 !--          In case of fast changes in the skin temperature, it is required to
    1238 !--          update the radiative fluxes in order to keep the solution stable
    1239              IF ( ABS( t_surface_p(j,i) - t_surface(j,i) ) > 0.2_wp )  THEN
     1243!--          In case of fast changes in the skin temperature, it is possible to
     1244!--          update the radiative fluxes independently from the prescribed
     1245!--          radiation call frequency. This effectively prevents oscillations,
     1246!--          especially when setting skip_time_do_radiation /= 0. The threshold
     1247!--          value of 0.2 used here is just a first guess. This method should be
     1248!--          revised in the future as tests have shown that the threshold is
     1249!--          often reached, when no oscillations would occur (causes immense
     1250!--          computing time for the radiation code).
     1251             IF ( ABS( t_surface_p(j,i) - t_surface(j,i) ) > 0.2_wp .AND.      &
     1252                  unscheduled_radiation_calls )  THEN
    12401253                force_radiation_call_l = .TRUE.
    12411254             ENDIF
     
    13881401!
    13891402!--    Make a logical OR for all processes. Force radiation call if at
    1390 !--    least one processor
    1391        IF ( intermediate_timestep_count == intermediate_timestep_count_max-1 ) &
    1392        THEN
     1403!--    least one processor reached the threshold change in skin temperature
     1404       IF ( unscheduled_radiation_calls .AND. intermediate_timestep_count      &
     1405            == intermediate_timestep_count_max-1 )  THEN
    13931406#if defined( __parallel )
    13941407          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     
    16281641!
    16291642!--             Account for dry soils (find a better solution here!)
    1630                 m_soil_p(:,j,i) = MAX(m_soil_p(:,j,i),0.0_wp)
     1643                DO  k = nzb_soil, nzt_soil
     1644                   IF ( m_soil_p(k,j,i) < 0.0_wp )  m_soil_p(k,j,i) = 0.0_wp
     1645                ENDDO
     1646
     1647
     1648
    16311649
    16321650!
Note: See TracChangeset for help on using the changeset viewer.