Ignore:
Timestamp:
Oct 26, 2015 4:17:44 PM (9 years ago)
Author:
maronga
Message:

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

File:
1 edited

Legend:

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

    r1683 r1691  
    1414! PALM. If not, see <http://www.gnu.org/licenses/>.
    1515!
    16 ! Copyright 1997-2014 Leibniz Universitaet Hannover
     16! Copyright 1997-2015 Leibniz Universitaet Hannover
    1717!--------------------------------------------------------------------------------!
    1818!
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Call to init_surface_layer added. rif is replaced by ol and zeta.
    2222!
    2323! Former revisions:
     
    266266               sums_l_l, sums_up_fraction_l, sums_wsts_bc_l, ts_value,         &
    267267               var_d, weight_pres, weight_substep
    268    
     268 
     269    USE surface_layer_fluxes_mod,                                              &
     270        ONLY:  init_surface_layer_fluxes
     271   
    269272    USE transpose_indices
    270273
     
    313316    ALLOCATE( ptdf_x(nxlg:nxrg), ptdf_y(nysg:nyng) )
    314317
    315     ALLOCATE( rif(nysg:nyng,nxlg:nxrg), shf(nysg:nyng,nxlg:nxrg),     &
     318    ALLOCATE( ol(nysg:nyng,nxlg:nxrg), shf(nysg:nyng,nxlg:nxrg),      &
    316319              ts(nysg:nyng,nxlg:nxrg), tswst(nysg:nyng,nxlg:nxrg),    &
    317320              us(nysg:nyng,nxlg:nxrg), usws(nysg:nyng,nxlg:nxrg),     &
     
    714717             hom(:,1,25,:) = SPREAD( l1d, 2, statistic_regions+1 )
    715718
    716              IF ( prandtl_layer )  THEN
    717                 rif  = rif1d(nzb+1)
     719             IF ( constant_flux_layer )  THEN
     720                ol   = ( zu(nzb+1) - zw(nzb) ) / rif1d(nzb+1)
    718721                ts   = 0.0_wp  ! could actually be computed more accurately in the
    719722                               ! 1D model. Update when opportunity arises.
     
    723726             ELSE
    724727                ts   = 0.0_wp  ! must be set, because used in
    725                 rif  = 0.0_wp  ! flowste
     728                ol   = ( zu(nzb+1) - zw(nzb) ) / zeta_min  ! flowste
    726729                us   = 0.0_wp
    727730                usws = 0.0_wp
     
    731734          ELSE
    732735             e    = 0.0_wp  ! must be set, because used in
    733              rif  = 0.0_wp  ! flowste
     736             ol   = ( zu(nzb+1) - zw(nzb) ) / zeta_min  ! flowste
    734737             ts   = 0.0_wp
    735738             us   = 0.0_wp
     
    886889             e    = 0.0_wp
    887890          ENDIF
    888           rif   = 0.0_wp
     891          ol    = ( zu(nzb+1) - zw(nzb) ) / zeta_min
    889892          ts    = 0.0_wp
    890893          us    = 0.0_wp
     
    10951098!
    10961099!--    Initialize Prandtl layer quantities
    1097        IF ( prandtl_layer )  THEN
     1100       IF ( constant_flux_layer )  THEN
    10981101
    10991102          z0 = roughness_length
     
    11031106!
    11041107!--          Surface temperature is prescribed. Here the heat flux cannot be
    1105 !--          simply estimated, because therefore rif, u* and theta* would have
     1108!--          simply estimated, because therefore ol, u* and theta* would have
    11061109!--          to be computed by iteration. This is why the heat flux is assumed
    11071110!--          to be zero before the first time step. It approaches its correct
     
    16241627       CALL location_message( 'initializing land surface model', .FALSE. )
    16251628       CALL init_lsm
     1629       CALL location_message( 'finished', .TRUE. )
     1630    ENDIF
     1631
     1632!
     1633!-- Initialize surface layer (done after LSM as roughness length are required
     1634!-- for initialization
     1635    IF ( constant_flux_layer )  THEN
     1636       CALL location_message( 'initializing surface layer', .FALSE. )
     1637       CALL init_surface_layer_fluxes
    16261638       CALL location_message( 'finished', .TRUE. )
    16271639    ENDIF
Note: See TracChangeset for help on using the changeset viewer.