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

    r1432 r1484  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Changes due to new module structure of the plant canopy model:
     23!   canopy-related initialization (e.g. lad and canopy_heat_flux) moved to new
     24!   subroutine init_plant_canopy within the module plant_canopy_model_mod,
     25!   call of subroutine init_plant_canopy added.
    2326!
    2427! Former revisions:
     
    217220    USE pegrid
    218221   
     222    USE plant_canopy_model_mod,                                                &
     223        ONLY:  init_plant_canopy, plant_canopy
     224   
    219225    USE random_function_mod
    220226   
     
    517523   
    518524!
    519 !-- 3D-arrays for the leaf area density and the canopy drag coefficient
    520     IF ( plant_canopy ) THEN
    521        ALLOCATE ( lad_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    522                   lad_u(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    523                   lad_v(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    524                   lad_w(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    525                   cdc(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    526 
    527        IF ( passive_scalar ) THEN
    528           ALLOCATE ( sls(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    529                      sec(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    530        ENDIF
    531 
    532        IF ( cthf /= 0.0_wp ) THEN
    533           ALLOCATE ( lai(nzb:nzt+1,nysg:nyng,nxlg:nxrg),  &
    534                      canopy_heat_flux(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    535        ENDIF
    536 
    537     ENDIF
    538 
    539 !
    540525!-- 4D-array for storing the Rif-values at vertical walls
    541526    IF ( topography /= 'flat' )  THEN
     
    15711556
    15721557!
    1573 !-- Initialization of the leaf area density
    1574     IF ( plant_canopy )  THEN
    1575  
    1576        SELECT CASE ( TRIM( canopy_mode ) )
    1577 
    1578           CASE( 'block' )
    1579 
    1580              DO  i = nxlg, nxrg
    1581                 DO  j = nysg, nyng
    1582                    lad_s(:,j,i) = lad(:)
    1583                    cdc(:,j,i)   = drag_coefficient
    1584                    IF ( passive_scalar )  THEN
    1585                       sls(:,j,i) = leaf_surface_concentration
    1586                       sec(:,j,i) = scalar_exchange_coefficient
    1587                    ENDIF
    1588                 ENDDO
    1589              ENDDO
    1590 
    1591           CASE DEFAULT
    1592 
    1593 !
    1594 !--          The DEFAULT case is reached either if the parameter
    1595 !--          canopy mode contains a wrong character string or if the
    1596 !--          user has coded a special case in the user interface.
    1597 !--          There, the subroutine user_init_plant_canopy checks
    1598 !--          which of these two conditions applies.
    1599              CALL user_init_plant_canopy
    1600  
    1601           END SELECT
    1602 
    1603        CALL exchange_horiz( lad_s, nbgp )
    1604        CALL exchange_horiz( cdc, nbgp )
    1605 
    1606        IF ( passive_scalar )  THEN
    1607           CALL exchange_horiz( sls, nbgp )
    1608           CALL exchange_horiz( sec, nbgp )
    1609        ENDIF
    1610 
    1611 !
    1612 !--    Sharp boundaries of the plant canopy in horizontal directions
    1613 !--    In vertical direction the interpolation is retained, as the leaf
    1614 !--    area density is initialised by prescribing a vertical profile
    1615 !--    consisting of piecewise linear segments. The upper boundary
    1616 !--    of the plant canopy is now defined by lad_w(pch_index,:,:) = 0.0.
    1617 
    1618        DO  i = nxl, nxr
    1619           DO  j = nys, nyn
    1620              DO  k = nzb, nzt+1
    1621                 IF ( lad_s(k,j,i) > 0.0_wp )  THEN
    1622                    lad_u(k,j,i)   = lad_s(k,j,i)
    1623                    lad_u(k,j,i+1) = lad_s(k,j,i)
    1624                    lad_v(k,j,i)   = lad_s(k,j,i)
    1625                    lad_v(k,j+1,i) = lad_s(k,j,i)
    1626                 ENDIF
    1627              ENDDO
    1628              DO  k = nzb, nzt
    1629                 lad_w(k,j,i) = 0.5_wp * ( lad_s(k+1,j,i) + lad_s(k,j,i) )
    1630              ENDDO
    1631           ENDDO
    1632        ENDDO
    1633 
    1634        lad_w(pch_index,:,:) = 0.0_wp
    1635        lad_w(nzt+1,:,:)     = lad_w(nzt,:,:)
    1636 
    1637        CALL exchange_horiz( lad_u, nbgp )
    1638        CALL exchange_horiz( lad_v, nbgp )
    1639        CALL exchange_horiz( lad_w, nbgp )
    1640 
    1641 !
    1642 !--    Initialisation of the canopy heat source distribution
    1643        IF ( cthf /= 0.0_wp )  THEN
    1644 !
    1645 !--       Piecewise evaluation of the leaf area index by
    1646 !--       integration of the leaf area density
    1647           lai(:,:,:) = 0.0_wp
    1648           DO  i = nxlg, nxrg
    1649              DO  j = nysg, nyng
    1650                 DO  k = pch_index-1, 0, -1
    1651                    lai(k,j,i) = lai(k+1,j,i) +                   &
    1652                                 ( 0.5_wp * ( lad_w(k+1,j,i) +    &
    1653                                           lad_s(k+1,j,i) ) *     &
    1654                                   ( zw(k+1) - zu(k+1) ) )  +     &
    1655                                 ( 0.5_wp * ( lad_w(k,j,i)   +    &
    1656                                           lad_s(k+1,j,i) ) *     &
    1657                                   ( zu(k+1) - zw(k) ) )
    1658                 ENDDO
    1659              ENDDO
    1660           ENDDO
    1661 
    1662 !
    1663 !--       Evaluation of the upward kinematic vertical heat flux within the
    1664 !--       canopy
    1665           DO  i = nxlg, nxrg
    1666              DO  j = nysg, nyng
    1667                 DO  k = 0, pch_index
    1668                    canopy_heat_flux(k,j,i) = cthf *                    &
    1669                                              exp( -0.6_wp * lai(k,j,i) )
    1670                 ENDDO
    1671              ENDDO
    1672           ENDDO
    1673 
    1674 !
    1675 !--       The near surface heat flux is derived from the heat flux
    1676 !--       distribution within the canopy
    1677           shf(:,:) = canopy_heat_flux(0,:,:)
    1678 
    1679        ENDIF
    1680 
    1681     ENDIF
     1558!-- If required, initialize quantities needed for the plant canopy model
     1559    IF ( plant_canopy )  CALL init_plant_canopy
    16821560
    16831561!
Note: See TracChangeset for help on using the changeset viewer.