Ignore:
Timestamp:
Jul 19, 2018 1:26:52 PM (6 years ago)
Author:
suehring
Message:

Further adjustments for surface structure

File:
1 edited

Legend:

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

    r3149 r3152  
    2626! -----------------
    2727! $Id$
     28! q_surface is now part of surface structure
     29!
     30! 3149 2018-07-19 05:48:09Z maronga
    2831! Correct accidental last commit
    2932!
     
    338341                CALL calc_pt_surface
    339342                IF ( humidity )  THEN
     343                   CALL calc_q_surface
    340344                   CALL calc_vpt_surface
    341345                ENDIF
     
    15951599
    15961600!
    1597 !-- Calculate potential temperature at first grid level
     1601!-- Set potential temperature at surface grid level.
    15981602!-- ( only for upward-facing surfs )
    15991603    SUBROUTINE calc_pt_surface
     
    16191623
    16201624!
    1621 !-- Calculate virtual potential temperature at first grid level
     1625!-- Set mixing ratio at surface grid level. ( Only for upward-facing surfs. )
     1626    SUBROUTINE calc_q_surface
     1627
     1628       IMPLICIT NONE
     1629
     1630       INTEGER(iwp) ::  k_off   !< index offset between surface and atmosphere grid point (-1 for upward-, +1 for downward-facing walls)
     1631       INTEGER(iwp) ::  m       !< loop variable over all horizontal surf elements
     1632       
     1633       k_off = surf%koff
     1634       !$OMP PARALLEL DO PRIVATE( i, j, k )
     1635       DO  m = 1, surf%ns
     1636
     1637          i   = surf%i(m)           
     1638          j   = surf%j(m)
     1639          k   = surf%k(m)
     1640
     1641          surf%q_surface(m) = q(k+k_off,j,i)
     1642
     1643       ENDDO
     1644
     1645    END SUBROUTINE calc_q_surface
     1646   
     1647!
     1648!-- Set virtual potential temperature at surface grid level.
    16221649!-- ( only for upward-facing surfs )
    16231650    SUBROUTINE calc_vpt_surface
     
    17811808                   z_mo = surf%z_mo(m)
    17821809
    1783                    surf%qs(m) = kappa * ( surf%qv1(m) - q(k-1,j,i) )           &
     1810                   surf%qs(m) = kappa * ( surf%qv1(m) - surf%q_surface(m) )    &
    17841811                                        / ( LOG( z_mo / surf%z0q(m) )          &
    17851812                                            - psi_h( z_mo / surf%ol(m) )       &
Note: See TracChangeset for help on using the changeset viewer.