Ignore:
Timestamp:
Jun 12, 2018 7:03:02 AM (6 years ago)
Author:
Giersch
Message:

New vertical stretching procedure has been introduced

File:
1 edited

Legend:

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

    r3049 r3065  
    2828! -----------------
    2929! $Id$
     30! Unused array dxdir was removed, dz was replaced by dzu to consider vertical
     31! grid stretching
     32!
     33! 3049 2018-05-29 13:52:36Z Giersch
    3034! Error messages revised
    3135!
     
    282286#if ! defined( __nopointer )
    283287    USE arrays_3d,                                                             &
    284         ONLY:  hyp, zu, pt, pt_1, pt_2, p, u, v, w, hyp, tend
     288        ONLY:  dzu, hyp, zu, pt, pt_1, pt_2, p, u, v, w, hyp, tend
    285289#endif
    286290
     
    292296   
    293297    USE control_parameters,                                                    &
    294         ONLY:  coupling_start_time, dz, topography, dt_3d,                     &
     298        ONLY:  coupling_start_time, topography, dt_3d,                         &
    295299               intermediate_timestep_count, initializing_actions,              &
    296300               intermediate_timestep_count_max, simulated_time, end_time,      &
     
    72077211        REAL(wp), DIMENSION(nzb:nzt)          :: exn                !< value of the Exner function in layers
    72087212       
    7209         REAL(wp), DIMENSION(0:4)              :: dxdir              !< surface normal direction gridbox length
    72107213        REAL(wp)                              :: dtime              !< simulated time of day (in UTC)
    72117214        INTEGER(iwp)                          :: dhour              !< simulated hour of day (in UTC)
     
    72137216
    72147217
    7215         dxdir = (/dz,dy,dy,dx,dx/)
    72167218#if ! defined( __nopointer )
    72177219        exn(nzb:nzt) = (hyp(nzb:nzt) / 100000.0_wp )**0.286_wp          !< Exner function
     
    76347636                         (dtime/3600.0_wp-REAL(dhour,wp))*aheatprof(k,dhour+1)
    76357637                 IF ( aheat(k,j,i) > 0.0_wp )  THEN
    7636                     pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exn(k)*rho_cp*dz)
     7638                    pt(k,j,i) = pt(k,j,i) + aheat(k,j,i)*acoef*dt_3d/(exn(k)*rho_cp*dzu(k))
    76377639                 ENDIF
    76387640              ENDIF
Note: See TracChangeset for help on using the changeset viewer.