Ignore:
Timestamp:
Jan 5, 2018 12:12:38 PM (6 years ago)
Author:
maronga
Message:

some changes in spinup mechanism and additional check in land surface model

File:
1 edited

Legend:

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

    r2723 r2724  
    2525! -----------------
    2626! $Id$
     27! Added security check for insufficient soil_temperature values
     28!
     29! 2723 2018-01-05 09:27:03Z maronga
    2730! Bugfix for spinups (end_time was increased twice in case of LSM + USM runs)
    2831!
     
    478481
    479482                                           
    480     REAL(wp), DIMENSION(0:20)  ::  root_fraction = 9999999.9_wp, & !< (NAMELIST) distribution of root surface area to the individual soil layers
    481                                    soil_moisture = 0.0_wp,       & !< NAMELIST soil moisture content (m3/m3)
    482                                    soil_temperature = 300.0_wp,  & !< NAMELIST soil temperature (K) +1
    483                                    dz_soil  = 9999999.9_wp,      & !< (NAMELIST) soil layer depths (spacing)
     483    REAL(wp), DIMENSION(0:20)  ::  root_fraction = 9999999.9_wp,     & !< (NAMELIST) distribution of root surface area to the individual soil layers
     484                                   soil_moisture = 0.0_wp,           & !< NAMELIST soil moisture content (m3/m3)
     485                                   soil_temperature = 9999999.9_wp,  & !< NAMELIST soil temperature (K) +1
     486                                   dz_soil  = 9999999.9_wp,          & !< (NAMELIST) soil layer depths (spacing)
    484487                                   zs_layer = 9999999.9_wp         !< soil layer depths (edge)
    485488                                 
     
    15091512    nzs = nzt_soil + 1
    15101513
    1511 
     1514!
     1515!-- Check whether valid soil temperatures are prescribed
     1516    IF ( ANY( soil_temperature(nzb_soil:nzt_soil+1) == 9999999.9_wp ) )  THEN
     1517       WRITE( message_string, * ) 'number of soil layers (', nzs, ') does not',&
     1518                                  ' match to the number of layers specified',  &
     1519                                  ' in soil_temperature (', COUNT(             &
     1520                                   soil_temperature /= 9999999.9_wp )-1, ')'
     1521          CALL message( 'check_parameters', 'PA0471', 1, 2, 0, 6, 0 )
     1522    ENDIF
     1523
     1524!
     1525!-- Check whether the sum of all root fractions equals one
    15121526    IF ( vegetation_type == 0 )  THEN
    15131527       IF ( SUM( root_fraction(nzb_soil:nzt_soil) ) /= 1.0_wp )  THEN
Note: See TracChangeset for help on using the changeset viewer.