Ignore:
Timestamp:
Oct 21, 2014 10:53:05 AM (10 years ago)
Author:
kanani
Message:

New:
---
Subroutine init_plant_canopy added to module plant_canopy_model_mod. (plant_canopy_model)
Alternative method for lad-profile construction added, also, new parameters added.
(header, package_parin, plant_canopy_model, read_var_list, write_var_list)
plant_canopy_model-dependency added to several subroutines. (Makefile)
New package/namelist canopy_par for canopy-related parameters added. (package_parin)

Changed:
---
Code structure of the plant canopy model changed, all canopy-model related code
combined to module plant_canopy_model_mod. (check_parameters, init_3d_model,
modules, timestep)
Module plant_canopy_model_mod added in USE-lists of some subroutines. (check_parameters,
header, init_3d_model, package_parin, read_var_list, user_init_plant_canopy, write_var_list)
Canopy initialization moved to new subroutine init_plant_canopy. (check_parameters,
init_3d_model, plant_canopy_model)
Calculation of canopy timestep-criterion removed, instead, the canopy
drag is now directly limited in the calculation of the canopy tendency terms.
(plant_canopy_model, timestep)
Some parameters renamed. (check_parameters, header, init_plant_canopy,
plant_canopy_model, read_var_list, write_var_list)
Unnecessary 3d-arrays removed. (init_plant_canopy, plant_canopy_model, user_init_plant_canopy)
Parameter checks regarding canopy initialization added. (check_parameters)
All canopy steering parameters moved from namelist inipar to canopy_par. (package_parin, parin)
Some redundant MPI communication removed. (init_plant_canopy)

Bugfix:
---
Missing KIND-attribute for REAL constant added. (check_parameters)
DO-WHILE-loop for lad-profile output restricted. (header)
Removed double-listing of use_upstream_for_tke in ONLY-list of module
control_parameters. (prognostic_equations)

File:
1 edited

Legend:

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

    r1368 r1484  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Changes due to new module structure of the plant canopy model:
     23!   module plant_canopy_model_mod added,
     24!   new package/namelist canopy_par added, i.e. the canopy model is no longer
     25!   steered over the inipar-namelist,
     26!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
     27!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff.
     28! Changed statement tags in CONTINUE-statement
    2329!
    2430! Former revisions:
     
    103109               write_particle_statistics
    104110
     111    USE plant_canopy_model_mod,                                                &
     112        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
     113               canopy_mode, cthf, lad_surface,                                 &
     114               lad_vertical_gradient, lad_vertical_gradient_level, lai_beta,   &
     115               leaf_scalar_exch_coeff, leaf_surface_conc, pch_index,           &
     116               plant_canopy
     117
    105118    USE spectrum,                                                              &
    106119        ONLY:  comp_spectra_level, data_output_sp, plot_spectra_level,         &
     
    110123
    111124    CHARACTER (LEN=80) ::  line  !:
     125
     126    NAMELIST /canopy_par/         alpha_lad, beta_lad, canopy_drag_coeff,      &
     127                                  canopy_mode, cthf,                           &
     128                                  lad_surface,                                 &
     129                                  lad_vertical_gradient,                       &
     130                                  lad_vertical_gradient_level,                 &
     131                                  lai_beta,                                    &
     132                                  leaf_scalar_exch_coeff,                      &
     133                                  leaf_surface_conc, pch_index
    112134
    113135    NAMELIST /dvrp_graphics_par/  clip_dvrp_l, clip_dvrp_n, clip_dvrp_r,       &
     
    159181    line = ' '
    160182
     183!
     184!-- Try to find canopy package
     185    REWIND ( 11 )
     186    line = ' '
     187    DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
     188       READ ( 11, '(A)', END=10 )  line
     189    ENDDO
     190    BACKSPACE ( 11 )
     191
     192!
     193!-- Read user-defined namelist
     194    READ ( 11, canopy_par )
     195
     196!
     197!-- Set flag that indicates that canopy model is switched on
     198    plant_canopy = .TRUE.
     199
     200!
     201!-- Set flag that indicates that the lad-profile shall be calculated by using
     202!-- a beta probability density function
     203    IF ( alpha_lad /= 9999999.9_wp  .AND.  beta_lad /= 9999999.9_wp )          &
     204       calc_beta_lad_profile = .TRUE.
     205
     206 10 CONTINUE
     207
     208
    161209#if defined( __dvrp_graphics )
    162210    REWIND ( 11 )
    163211    line = ' '
    164212    DO   WHILE ( INDEX( line, '&dvrp_graphics_par' ) == 0 )
    165        READ ( 11, '(A)', END=10 )  line
     213       READ ( 11, '(A)', END=20 )  line
    166214    ENDDO
    167215    BACKSPACE ( 11 )
     
    171219    READ ( 11, dvrp_graphics_par )
    172220
    173  10 CONTINUE
     221 20 CONTINUE
    174222#endif
    175223
     
    179227    line = ' '
    180228    DO   WHILE ( INDEX( line, '&particles_par' ) == 0 )
    181        READ ( 11, '(A)', END=20 )  line
     229       READ ( 11, '(A)', END=30 )  line
    182230    ENDDO
    183231    BACKSPACE ( 11 )
     
    191239    particle_advection = .TRUE.
    192240
    193  20 CONTINUE
     241 30 CONTINUE
    194242
    195243
     
    198246    line = ' '
    199247    DO   WHILE ( INDEX( line, '&spectra_par' ) == 0 )
    200        READ ( 11, '(A)', END=30 )  line
     248       READ ( 11, '(A)', END=40 )  line
    201249    ENDDO
    202250    BACKSPACE ( 11 )
     
    211259    IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
    212260
    213  30 CONTINUE
     261 40 CONTINUE
    214262#endif
    215263
Note: See TracChangeset for help on using the changeset viewer.