Ignore:
Timestamp:
Feb 8, 2018 1:24:35 PM (6 years ago)
Author:
suehring
Message:

Output of ground-heat flux at natural- and urban-type surfaces in one output variable; enable restart data of _av variables that belong to both land- and urban-surface model

File:
1 edited

Legend:

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

    r2790 r2797  
    2525! -----------------
    2626! $Id$
     27! Enable output of ground-heat flux also at urban surfaces.
     28!
     29! 2790 2018-02-06 11:57:19Z suehring
    2730! Bugfix in summation of surface sensible and latent heat flux
    2831!
     
    172175
    173176    USE averaging,                                                             &
    174         ONLY:  diss_av, e_av, kh_av, km_av, lpt_av, lwp_av, nc_av, nr_av,      &
     177        ONLY:  diss_av, e_av, ghf_av, kh_av, km_av, lpt_av, lwp_av, nc_av,     &
     178               nr_av,                                                          &
    175179               ol_av, p_av, pc_av, pr_av, prr_av, precipitation_rate_av, pt_av,&
    176180               q_av, qc_av, ql_av, ql_c_av, ql_v_av, ql_vp_av, qr_av, qsws_av, &
     
    255259          SELECT CASE ( trimvar )
    256260
     261             CASE ( 'ghf*' )
     262                IF ( .NOT. ALLOCATED( ghf_av ) )  THEN
     263                   ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
     264                ENDIF
     265                ghf_av = 0.0_wp
     266
    257267             CASE ( 'e' )
    258268                IF ( .NOT. ALLOCATED( e_av ) )  THEN
     
    538548!--    Store the array chosen on the temporary array.
    539549       SELECT CASE ( trimvar )
     550
     551          CASE ( 'ghf*' )
     552             DO  m = 1, surf_lsm_h%ns
     553                i   = surf_lsm_h%i(m)           
     554                j   = surf_lsm_h%j(m)
     555                ghf_av(j,i) = ghf_av(j,i) + surf_lsm_h%ghf(m)
     556             ENDDO
     557
     558             DO  m = 1, surf_usm_h%ns
     559                i   = surf_usm_h%i(m)           
     560                j   = surf_usm_h%j(m)
     561                ghf_av(j,i) = ghf_av(j,i) + surf_usm_h%frac(0,m)     *          &
     562                                            surf_usm_h%wghf_eb(m)        +      &
     563                                            surf_usm_h%frac(1,m)     *          &
     564                                            surf_usm_h%wghf_eb_green(m)  +      &
     565                                            surf_usm_h%frac(2,m)     *          &
     566                                            surf_usm_h%wghf_eb_window(m)
     567             ENDDO
    540568
    541569          CASE ( 'e' )
Note: See TracChangeset for help on using the changeset viewer.