Ignore:
Timestamp:
Dec 16, 2019 10:43:49 AM (5 years ago)
Author:
motisi
Message:

plant_canopy_model: unification of variable names: pc_ variabels now pcm_ variables
removal of bowenratio output
canopy mode 'block' now 'homogeneous'
'read_from_file_3d' now 'read_from_file'
removal of confusing comment lines
replacement of k_wall by topo_top_ind
removal of else-statement in tendency-calculation

File:
1 edited

Legend:

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

    r4340 r4341  
    2828! -----------------
    2929! $Id$
     30! Renamed pc_heating_rate, pc_transpiration_rate, pc_transpiration_rate to
     31! pcm_heating_rate, pcm_latent_rate, pcm_transpiration_rate
     32!
     33! 4340 2019-12-16 08:17:03Z Giersch
    3034! Albedo indices for building_surface_pars are now declared as parameters to
    3135! prevent an error if the gfortran compiler with -Werror=unused-value is used
     
    302306
    303307    USE plant_canopy_model_mod,                                                &
    304         ONLY:  lad_s, pc_heating_rate, pc_transpiration_rate, pc_latent_rate,  &
    305                plant_canopy_transpiration, pcm_calc_transpiration_rate
     308        ONLY:  lad_s,                                                          &
     309               pcm_heating_rate,                                               &
     310               pcm_transpiration_rate,                                         &
     311               pcm_latent_rate,                                                &
     312               plant_canopy_transpiration,                                     &
     313               pcm_calc_transpiration_rate
    306314
    307315    USE pegrid
     
    61506158!--  push heat flux absorbed by plant canopy to respective 3D arrays
    61516159     IF ( npcbl > 0 )  THEN
    6152          pc_heating_rate(:,:,:) = 0.0_wp
     6160         pcm_heating_rate(:,:,:) = 0.0_wp
    61536161         DO ipcgb = 1, npcbl
    61546162             j = pcbl(iy, ipcgb)
     
    61586166!--          Following expression equals former kk = k - nzb_s_inner(j,i)
    61596167             kk = k - topo_top_ind(j,i,0)  !- lad arrays are defined flat
    6160              pc_heating_rate(kk, j, i) = (pcbinsw(ipcgb) + pcbinlw(ipcgb)) &
     6168             pcm_heating_rate(kk, j, i) = (pcbinsw(ipcgb) + pcbinlw(ipcgb)) &
    61616169                 * pchf_prep(k) * pt(k, j, i) !-- = dT/dt
    61626170         ENDDO
     
    61646172         IF ( humidity .AND. plant_canopy_transpiration ) THEN
    61656173!--          Calculation of plant canopy transpiration rate and correspondidng latent heat rate
    6166              pc_transpiration_rate(:,:,:) = 0.0_wp
    6167              pc_latent_rate(:,:,:) = 0.0_wp
     6174             pcm_transpiration_rate(:,:,:) = 0.0_wp
     6175             pcm_latent_rate(:,:,:) = 0.0_wp
    61686176             DO ipcgb = 1, npcbl
    61696177                 i = pcbl(ix, ipcgb)
     
    61726180                 kk = k - topo_top_ind(j,i,0)  !- lad arrays are defined flat
    61736181                 CALL pcm_calc_transpiration_rate( i, j, k, kk, pcbinsw(ipcgb), pcbinlw(ipcgb), &
    6174                                                    pc_transpiration_rate(kk,j,i), pc_latent_rate(kk,j,i) )
     6182                                                   pcm_transpiration_rate(kk,j,i), pcm_latent_rate(kk,j,i) )
    61756183              ENDDO
    61766184         ENDIF
Note: See TracChangeset for help on using the changeset viewer.