Ignore:
Timestamp:
Apr 30, 2014 12:15:41 PM (10 years ago)
Author:
boeske
Message:

minor changes in profile data output of lsf tendencies, variables renamed

File:
1 edited

Legend:

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

    r1381 r1382  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Changed the weighting factor that is used in the summation of subsidence
     23! tendencies for profile data output from weight_pres to weight_substep
     24! added Neumann boundary conditions for profile data output of subsidence terms
     25! at nzt+1
    2326!
    2427! Former revisions:
     
    163166
    164167       USE statistics,                                                         &
    165            ONLY:  sums_ls_l, weight_pres
     168           ONLY:  sums_ls_l, weight_substep
    166169
    167170       IMPLICIT NONE
     
    186189       DO  i = nxl, nxr
    187190          DO  j = nys, nyn
     191
    188192             DO  k = nzb_s_inner(j,i)+1, nzt
    189193                IF ( w_subs(k) < 0.0_wp )  THEN    ! large-scale subsidence
     
    199203                IF ( large_scale_forcing )  THEN
    200204                   sums_ls_l(k,ls_index) = sums_ls_l(k,ls_index) + tmp_tend    &
    201                                       * weight_pres(intermediate_timestep_count)
     205                                   * weight_substep(intermediate_timestep_count)
    202206                ENDIF
    203207             ENDDO
     208
     209             sums_ls_l(nzt+1,ls_index) = sums_ls_l(nzt,ls_index)
     210
    204211          ENDDO
    205212       ENDDO
     
    259266
    260267       USE statistics,                                                         &
    261            ONLY:  sums_ls_l, weight_pres
     268           ONLY:  sums_ls_l, weight_substep
    262269
    263270       IMPLICIT NONE
     
    291298          IF ( large_scale_forcing )  THEN
    292299             sums_ls_l(k,ls_index) = sums_ls_l(k,ls_index) + tmp_tend          &
    293                                      * weight_pres(intermediate_timestep_count)
     300                                   * weight_substep(intermediate_timestep_count)
    294301          ENDIF
    295302       ENDDO
     303
     304       sums_ls_l(nzt+1,ls_index) = sums_ls_l(nzt,ls_index)
    296305
    297306
Note: See TracChangeset for help on using the changeset viewer.