Ignore:
Timestamp:
Apr 29, 2019 3:09:07 PM (5 years ago)
Author:
suehring
Message:

Move initialization of STG behind initialization of offline nesting; Bugfix in STG in case of very early restart; calculation of scaling parameters used for parametrization of synthetic turbulence profiles improved; in offline nesting, set boundary value at upper-left and upper-south grid points for u- and v-component, respectively

File:
1 edited

Legend:

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

    r3891 r3937  
    2525! -----------------
    2626! $Id$
     27! Set boundary conditon on upper-left and upper-south grid point for the u- and
     28! v-component, respectively.
     29!
     30! 3891 2019-04-12 17:52:01Z suehring
    2731! Bugfix, do not overwrite lateral and top boundary data in case of restart
    2832! runs.
     
    633637          ENDDO
    634638       ENDDO
     639!
     640!--    For left boundary set boundary condition for u-component also at top
     641!--    grid point.
     642!--    Note, this has no effect on the numeric solution, only for data output.
     643       IF ( bc_dirichlet_l )  u(nzt+1,:,nxl) = u(nzt+1,:,nxlu)
    635644
    636645       DO  i = nxl, nxr
     
    644653          ENDDO
    645654       ENDDO
     655!
     656!--    For south boundary set boundary condition for v-component also at top
     657!--    grid point.
     658!--    Note, this has no effect on the numeric solution, only for data output.
     659       IF ( bc_dirichlet_s )  v(nzt+1,nys,:) = v(nzt+1,nysv,:)
    646660
    647661       DO  i = nxl, nxr
     
    961975       topo_max     = topo_max_l
    962976#endif
    963 
    964977       zi_ribulk = MAX( zi_ribulk, topo_max )
    965 
     978       
    966979    END SUBROUTINE calc_zi
    967980   
Note: See TracChangeset for help on using the changeset viewer.