Ignore:
Timestamp:
Nov 28, 2007 10:03:58 AM (16 years ago)
Author:
letzel
Message:

Plant canopy model of Watanabe (2004,BLM 112,307-341) added.

File:
1 edited

Legend:

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

    r132 r138  
    44! Actual revisions:
    55! -----------------
     6! Plant canopy added
    67! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
    78! Multigrid solver allows topography, checking of dt_sort_particles
     
    592593    ENDIF
    593594
     595    IF ( plant_canopy .AND. ( drag_coefficient == 0.0 ) ) THEN
     596       IF ( myid == 0 )  PRINT*, '+++ check_parameters: plant_canopy = TRUE', &
     597                                 'requires a non-zero drag_coefficient'
     598       CALL local_stop
     599    ENDIF
     600
    594601!
    595602!-- In case of no model continuation run, check initialising parameters and
     
    605612       IF ( ocean )           sa_init = sa_surface
    606613       IF ( passive_scalar )  q_init  = s_surface
     614       IF ( plant_canopy )    lad = 0.0
    607615
    608616!
     
    934942       ENDIF
    935943
    936     ENDIF
    937 
     944!
     945!--    If required compute the profile of leaf area density used in the plant canopy model
     946       IF ( plant_canopy ) THEN
     947       
     948          i = 1
     949          gradient = 0.0
     950
     951          IF ( .NOT. ocean ) THEN
     952 
     953             lad_vertical_gradient_level_ind(1) = 0
     954             DO k = 1, pch_index
     955                IF ( lad_vertical_gradient_level(i) < zu(k) .AND.  &
     956                     lad_vertical_gradient_level(i) >= 0.0 ) THEN
     957                   gradient = lad_vertical_gradient(i)
     958                   lad_vertical_gradient_level_ind(i) = k - 1
     959                   i = i + 1
     960                   IF ( i > 10 ) THEN
     961                      IF ( myid == 0 ) THEN
     962                         PRINT*, '+++ user_init_3d_model: upper bound 10 of array',  &
     963                                 ' "lad_vertical_gradient_level" exceeded'
     964                      ENDIF
     965                      CALL local_stop
     966                   ENDIF
     967                ENDIF
     968                IF ( gradient /= 0.0 ) THEN
     969                   IF ( k /= 1 ) THEN
     970                      lad(k) = lad(k-1) + dzu(k) * gradient
     971                   ELSE
     972                      lad(k) = lad_surface + 0.5 * dzu(k) *gradient
     973                   ENDIF
     974                ELSE
     975                   lad(k) = lad(k-1)
     976                ENDIF
     977             ENDDO
     978
     979          ENDIF
     980
     981!
     982!--       In case of no given leaf area density gradients, choose a vanishing gradient
     983          IF ( lad_vertical_gradient_level(1) == -9999999.9 ) THEN
     984             lad_vertical_gradient_level(1) = 0.0
     985          ENDIF
     986
     987       ENDIF
     988         
     989    ENDIF
     990             
    938991!
    939992!-- Compute Coriolis parameter
Note: See TracChangeset for help on using the changeset viewer.