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/user_init_plant_canopy.f90

    r1354 r1484  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Changes in the course of the canopy-model modularization:
     23!   module plant_canopy_model_mod added,
     24!   definition of array cdc (canopy drag coefficient) removed, since it is now
     25!   defined purely as a single constant value (see module plant_canopy_model)
    2326!
    2427! Former revisions:
     
    5760   
    5861    USE kinds
     62
     63    USE plant_canopy_model_mod
    5964   
    6065    USE user
     
    6267    IMPLICIT NONE
    6368
    64     INTEGER(iwp) :: i   !:
    65     INTEGER(iwp) :: j   !:
     69    INTEGER(iwp) :: i   !: running index
     70    INTEGER(iwp) :: j   !: running index
    6671
    6772!
     
    6974
    7075!
    71 !-- Set the 3D-arrays lad_s and cdc for user defined canopies
     76!-- Set the 3D-array lad_s for user defined canopies
    7277    SELECT CASE ( TRIM( canopy_mode ) )
    7378
     
    7883       CASE ( 'user_defined_canopy_1' )
    7984!
    80 !--       Here the user can define his own topography.
    81 !--       The following lines contain an example in that the
    82 !--       plant canopy extends only over the second half of the
    83 !--       model domain along x
     85!--       Here the user can define his own forest topography.
     86!--       The following lines contain an example, where the plant canopy extends
     87!--       only over the second half of the model domain along x.
     88!--       Attention: DO-loops have to include the ghost points (nxlg-nxrg,
     89!--       nysg-nyng), because no exchange of ghost point information is intended,
     90!--       in order to minimize communication between CPUs
    8491!          DO  i = nxlg, nxrg
    8592!             IF ( i >= INT(nx+1/2) ) THEN
    8693!                DO  j = nysg, nyng
    8794!                   lad_s(:,j,i) = lad(:)
    88 !                   cdc(:,j,i)   = drag_coefficient
    8995!                ENDDO
    9096!             ELSE
    9197!                lad_s(:,:,i) = 0.0_wp
    92 !                cdc(:,:,i)   = 0.0_wp
    9398!             ENDIF
    9499!          ENDDO
     100!
    95101!--       After definition, please
    96102!--       remove the following three lines!
Note: See TracChangeset for help on using the changeset viewer.