Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

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

    r1485 r1682  
    1  MODULE plant_canopy_model_mod
    2 
     1!> @file plant_canopy_model.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6665! Description:
    6766! ------------
    68 ! 1) Initialization of the canopy model, e.g. construction of leaf area density
    69 ! profile (subroutine init_plant_canopy).
    70 ! 2) Calculation of sinks and sources of momentum, heat and scalar concentration
    71 ! due to canopy elements (subroutine plant_canopy_model).
     67!> 1) Initialization of the canopy model, e.g. construction of leaf area density
     68!> profile (subroutine init_plant_canopy).
     69!> 2) Calculation of sinks and sources of momentum, heat and scalar concentration
     70!> due to canopy elements (subroutine plant_canopy_model).
    7271!------------------------------------------------------------------------------!
     72 MODULE plant_canopy_model_mod
     73 
    7374    USE arrays_3d,                                                             &
    7475        ONLY:  dzu, dzw, e, q, shf, tend, u, v, w, zu, zw
     
    8485
    8586
    86     CHARACTER (LEN=20)   ::  canopy_mode = 'block' !: canopy coverage
    87 
    88     INTEGER(iwp) ::  pch_index = 0                 !: plant canopy height/top index
     87    CHARACTER (LEN=20)   ::  canopy_mode = 'block' !< canopy coverage
     88
     89    INTEGER(iwp) ::  pch_index = 0                 !< plant canopy height/top index
    8990    INTEGER(iwp) ::                                                            &
    90        lad_vertical_gradient_level_ind(10) = -9999 !: lad-profile levels (index)
    91 
    92     LOGICAL ::  calc_beta_lad_profile = .FALSE. !: switch for calc. of lad from beta func.
    93     LOGICAL ::  plant_canopy = .FALSE.          !: switch for use of canopy model
    94 
    95     REAL(wp) ::  alpha_lad = 9999999.9_wp   !: coefficient for lad calculation
    96     REAL(wp) ::  beta_lad = 9999999.9_wp    !: coefficient for lad calculation
    97     REAL(wp) ::  canopy_drag_coeff = 0.0_wp !: canopy drag coefficient (parameter)
    98     REAL(wp) ::  cdc = 0.0_wp               !: canopy drag coeff. (abbreviation used in equations)
    99     REAL(wp) ::  cthf = 0.0_wp              !: canopy top heat flux
    100     REAL(wp) ::  dt_plant_canopy = 0.0_wp   !: timestep account. for canopy drag
    101     REAL(wp) ::  lad_surface = 0.0_wp       !: lad surface value
    102     REAL(wp) ::  lai_beta = 0.0_wp          !: leaf area index (lai) for lad calc.
     91       lad_vertical_gradient_level_ind(10) = -9999 !< lad-profile levels (index)
     92
     93    LOGICAL ::  calc_beta_lad_profile = .FALSE. !< switch for calc. of lad from beta func.
     94    LOGICAL ::  plant_canopy = .FALSE.          !< switch for use of canopy model
     95
     96    REAL(wp) ::  alpha_lad = 9999999.9_wp   !< coefficient for lad calculation
     97    REAL(wp) ::  beta_lad = 9999999.9_wp    !< coefficient for lad calculation
     98    REAL(wp) ::  canopy_drag_coeff = 0.0_wp !< canopy drag coefficient (parameter)
     99    REAL(wp) ::  cdc = 0.0_wp               !< canopy drag coeff. (abbreviation used in equations)
     100    REAL(wp) ::  cthf = 0.0_wp              !< canopy top heat flux
     101    REAL(wp) ::  dt_plant_canopy = 0.0_wp   !< timestep account. for canopy drag
     102    REAL(wp) ::  lad_surface = 0.0_wp       !< lad surface value
     103    REAL(wp) ::  lai_beta = 0.0_wp          !< leaf area index (lai) for lad calc.
    103104    REAL(wp) ::                                                                &
    104        leaf_scalar_exch_coeff = 0.0_wp      !: canopy scalar exchange coeff.
     105       leaf_scalar_exch_coeff = 0.0_wp      !< canopy scalar exchange coeff.
    105106    REAL(wp) ::                                                                &
    106        leaf_surface_conc = 0.0_wp           !: leaf surface concentration
    107     REAL(wp) ::  lsec = 0.0_wp              !: leaf scalar exchange coeff.
    108     REAL(wp) ::  lsc = 0.0_wp               !: leaf surface concentration
     107       leaf_surface_conc = 0.0_wp           !< leaf surface concentration
     108    REAL(wp) ::  lsec = 0.0_wp              !< leaf scalar exchange coeff.
     109    REAL(wp) ::  lsc = 0.0_wp               !< leaf surface concentration
    109110
    110111    REAL(wp) ::                                                                &
    111        lad_vertical_gradient(10) = 0.0_wp              !: lad gradient
     112       lad_vertical_gradient(10) = 0.0_wp              !< lad gradient
    112113    REAL(wp) ::                                                                &
    113        lad_vertical_gradient_level(10) = -9999999.9_wp !: lad-prof. levels (in m)
    114 
    115     REAL(wp), DIMENSION(:), ALLOCATABLE ::  lad            !: leaf area density
    116     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !: preliminary lad
     114       lad_vertical_gradient_level(10) = -9999999.9_wp !< lad-prof. levels (in m)
     115
     116    REAL(wp), DIMENSION(:), ALLOCATABLE ::  lad            !< leaf area density
     117    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !< preliminary lad
    117118   
    118119    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::                                 &
    119        canopy_heat_flux                                    !: canopy heat flux
    120     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf !: cumulative lai for heatflux calc.
    121     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s      !: lad on scalar-grid
     120       canopy_heat_flux                                    !< canopy heat flux
     121    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf !< cumulative lai for heatflux calc.
     122    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s      !< lad on scalar-grid
    122123
    123124
     
    152153! Description:
    153154! ------------
    154 !-- Initialization of the plant canopy model
     155!> Initialization of the plant canopy model
    155156!------------------------------------------------------------------------------!
    156157    SUBROUTINE init_plant_canopy
     
    163164       IMPLICIT NONE
    164165
    165        INTEGER(iwp) ::  i !: running index
    166        INTEGER(iwp) ::  j !: running index
    167        INTEGER(iwp) ::  k !: running index
    168 
    169        REAL(wp) ::  int_bpdf      !: vertical integral for lad-profile construction
    170        REAL(wp) ::  dzh           !: vertical grid spacing in units of canopy height
    171        REAL(wp) ::  gradient      !: gradient for lad-profile construction
    172        REAL(wp) ::  canopy_height !: canopy height for lad-profile construction
     166       INTEGER(iwp) ::  i !< running index
     167       INTEGER(iwp) ::  j !< running index
     168       INTEGER(iwp) ::  k !< running index
     169
     170       REAL(wp) ::  int_bpdf      !< vertical integral for lad-profile construction
     171       REAL(wp) ::  dzh           !< vertical grid spacing in units of canopy height
     172       REAL(wp) ::  gradient      !< gradient for lad-profile construction
     173       REAL(wp) ::  canopy_height !< canopy height for lad-profile construction
    173174
    174175!
     
    368369! Description:
    369370! ------------
    370 !-- Calculation of the tendency terms, accounting for the effect of the plant
    371 !-- canopy on momentum and scalar quantities.
    372 !--
    373 !-- The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
    374 !-- (defined on scalar grid), as initialized in subroutine init_plant_canopy.
    375 !-- The lad on the w-grid is vertically interpolated from the surrounding
    376 !-- lad_s. The upper boundary of the canopy is defined on the w-grid at
    377 !-- k = pch_index. Here, the lad is zero.
    378 !--
    379 !-- The canopy drag must be limited (previously accounted for by calculation of
    380 !-- a limiting canopy timestep for the determination of the maximum LES timestep
    381 !-- in subroutine timestep), since it is physically impossible that the canopy
    382 !-- drag alone can locally change the sign of a velocity component. This
    383 !-- limitation is realized by calculating preliminary tendencies and velocities.
    384 !-- It is subsequently checked if the preliminary new velocity has a different
    385 !-- sign than the current velocity. If so, the tendency is limited in a way that
    386 !-- the velocity can at maximum be reduced to zero by the canopy drag.
    387 !--
    388 !--
    389 !-- Call for all grid points
     371!> Calculation of the tendency terms, accounting for the effect of the plant
     372!> canopy on momentum and scalar quantities.
     373!>
     374!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
     375!> (defined on scalar grid), as initialized in subroutine init_plant_canopy.
     376!> The lad on the w-grid is vertically interpolated from the surrounding
     377!> lad_s. The upper boundary of the canopy is defined on the w-grid at
     378!> k = pch_index. Here, the lad is zero.
     379!>
     380!> The canopy drag must be limited (previously accounted for by calculation of
     381!> a limiting canopy timestep for the determination of the maximum LES timestep
     382!> in subroutine timestep), since it is physically impossible that the canopy
     383!> drag alone can locally change the sign of a velocity component. This
     384!> limitation is realized by calculating preliminary tendencies and velocities.
     385!> It is subsequently checked if the preliminary new velocity has a different
     386!> sign than the current velocity. If so, the tendency is limited in a way that
     387!> the velocity can at maximum be reduced to zero by the canopy drag.
     388!>
     389!>
     390!> Call for all grid points
    390391!------------------------------------------------------------------------------!
    391392    SUBROUTINE plant_canopy_model( component )
     
    399400       IMPLICIT NONE
    400401
    401        INTEGER(iwp) ::  component !: prognostic variable (u,v,w,pt,q,e)
    402        INTEGER(iwp) ::  i         !: running index
    403        INTEGER(iwp) ::  j         !: running index
    404        INTEGER(iwp) ::  k         !: running index
    405 
    406        REAL(wp) ::  ddt_3d    !: inverse of the LES timestep (dt_3d)
    407        REAL(wp) ::  lad_local !: local lad value
    408        REAL(wp) ::  pre_tend  !: preliminary tendency
    409        REAL(wp) ::  pre_u     !: preliminary u-value
    410        REAL(wp) ::  pre_v     !: preliminary v-value
    411        REAL(wp) ::  pre_w     !: preliminary w-value
     402       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
     403       INTEGER(iwp) ::  i         !< running index
     404       INTEGER(iwp) ::  j         !< running index
     405       INTEGER(iwp) ::  k         !< running index
     406
     407       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
     408       REAL(wp) ::  lad_local !< local lad value
     409       REAL(wp) ::  pre_tend  !< preliminary tendency
     410       REAL(wp) ::  pre_u     !< preliminary u-value
     411       REAL(wp) ::  pre_v     !< preliminary v-value
     412       REAL(wp) ::  pre_w     !< preliminary w-value
    412413
    413414
     
    659660! Description:
    660661! ------------
    661 !-- Calculation of the tendency terms, accounting for the effect of the plant
    662 !-- canopy on momentum and scalar quantities.
    663 !--
    664 !-- The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
    665 !-- (defined on scalar grid), as initialized in subroutine init_plant_canopy.
    666 !-- The lad on the w-grid is vertically interpolated from the surrounding
    667 !-- lad_s. The upper boundary of the canopy is defined on the w-grid at
    668 !-- k = pch_index. Here, the lad is zero.
    669 !--
    670 !-- The canopy drag must be limited (previously accounted for by calculation of
    671 !-- a limiting canopy timestep for the determination of the maximum LES timestep
    672 !-- in subroutine timestep), since it is physically impossible that the canopy
    673 !-- drag alone can locally change the sign of a velocity component. This
    674 !-- limitation is realized by calculating preliminary tendencies and velocities.
    675 !-- It is subsequently checked if the preliminary new velocity has a different
    676 !-- sign than the current velocity. If so, the tendency is limited in a way that
    677 !-- the velocity can at maximum be reduced to zero by the canopy drag.
    678 !--
    679 !--
    680 !-- Call for grid point i,j
     662!> Calculation of the tendency terms, accounting for the effect of the plant
     663!> canopy on momentum and scalar quantities.
     664!>
     665!> The canopy is located where the leaf area density lad_s(k,j,i) > 0.0
     666!> (defined on scalar grid), as initialized in subroutine init_plant_canopy.
     667!> The lad on the w-grid is vertically interpolated from the surrounding
     668!> lad_s. The upper boundary of the canopy is defined on the w-grid at
     669!> k = pch_index. Here, the lad is zero.
     670!>
     671!> The canopy drag must be limited (previously accounted for by calculation of
     672!> a limiting canopy timestep for the determination of the maximum LES timestep
     673!> in subroutine timestep), since it is physically impossible that the canopy
     674!> drag alone can locally change the sign of a velocity component. This
     675!> limitation is realized by calculating preliminary tendencies and velocities.
     676!> It is subsequently checked if the preliminary new velocity has a different
     677!> sign than the current velocity. If so, the tendency is limited in a way that
     678!> the velocity can at maximum be reduced to zero by the canopy drag.
     679!>
     680!>
     681!> Call for grid point i,j
    681682!------------------------------------------------------------------------------!
    682683    SUBROUTINE plant_canopy_model_ij( i, j, component )
     
    690691       IMPLICIT NONE
    691692
    692        INTEGER(iwp) ::  component !: prognostic variable (u,v,w,pt,q,e)
    693        INTEGER(iwp) ::  i         !: running index
    694        INTEGER(iwp) ::  j         !: running index
    695        INTEGER(iwp) ::  k         !: running index
    696 
    697        REAL(wp) ::  ddt_3d    !: inverse of the LES timestep (dt_3d)
    698        REAL(wp) ::  lad_local !: local lad value
    699        REAL(wp) ::  pre_tend  !: preliminary tendency
    700        REAL(wp) ::  pre_u     !: preliminary u-value
    701        REAL(wp) ::  pre_v     !: preliminary v-value
    702        REAL(wp) ::  pre_w     !: preliminary w-value
     693       INTEGER(iwp) ::  component !< prognostic variable (u,v,w,pt,q,e)
     694       INTEGER(iwp) ::  i         !< running index
     695       INTEGER(iwp) ::  j         !< running index
     696       INTEGER(iwp) ::  k         !< running index
     697
     698       REAL(wp) ::  ddt_3d    !< inverse of the LES timestep (dt_3d)
     699       REAL(wp) ::  lad_local !< local lad value
     700       REAL(wp) ::  pre_tend  !< preliminary tendency
     701       REAL(wp) ::  pre_u     !< preliminary u-value
     702       REAL(wp) ::  pre_v     !< preliminary v-value
     703       REAL(wp) ::  pre_w     !< preliminary w-value
    703704
    704705
Note: See TracChangeset for help on using the changeset viewer.