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/init_masks.f90

    r3049 r3065  
    2525! -----------------
    2626! $Id$
     27! dz_stretch_level was replaced by dz_stretch_level_start
     28!
     29! 3049 2018-05-29 13:52:36Z Giersch
    2730! Error messages revised
    2831!
     
    133136        ONLY:  constant_diffusion, cloud_droplets, cloud_physics,              &
    134137               data_output_masks, data_output_masks_user,                      &
    135                doav, doav_n, domask, domask_no, dz, dz_stretch_level, humidity,&
    136                mask, masks, mask_scale, mask_i,                                &
     138               doav, doav_n, domask, domask_no, dz, dz_stretch_level_start,    &
     139               humidity, mask, masks, mask_scale, mask_i,                      &
    137140               mask_i_global, mask_j, mask_j_global, mask_k, mask_k_global,    &
    138141               mask_loop, mask_size, mask_size_l, mask_start_l, mask_x,        &
     
    141144               microphysics_morrison, microphysics_seifert, passive_scalar,    &
    142145               ocean, varnamelength
     146               
    143147
    144148    USE grid_variables,                                                        &
     
    490494       CALL set_mask_locations( 1, dx, 'dx', nx, 'nx', nxl, nxr )
    491495       CALL set_mask_locations( 2, dy, 'dy', ny, 'ny', nys, nyn )
    492        CALL set_mask_locations( 3, dz, 'dz', nz, 'nz', nzb, nzt )
     496       CALL set_mask_locations( 3, dz(1), 'dz', nz, 'nz', nzb, nzt )
    493497!
    494498!--    Set global masks along all three dimensions (required by
     
    727731!--          The following line assumes a constant vertical grid spacing within
    728732!--          the vertical mask range; it fails for vertical grid stretching.
    729 !--          Maybe revise later. Issue warning but continue execution.
     733!--          Maybe revise later. Issue warning but continue execution. ABS(...)
     734!--          within the IF statement is necessary because the default value of
     735!--          dz_stretch_level_start is -9999999.9_wp.
    730736             loop_stride = NINT( mask_loop(mid,dim,3) * mask_scale(dim) * ddxyz )
    731737
    732              IF ( mask_loop(mid,dim,2) * mask_scale(dim) > dz_stretch_level )  &
    733                   THEN
     738             IF ( mask_loop(mid,dim,2) * mask_scale(dim) >                     &
     739                  ABS( dz_stretch_level_start(1) ) )  THEN
    734740                WRITE ( message_string, '(A,I3,A,I1,A,F9.3,A,F8.2,3A)' )       &
    735741                     'mask_loop(',mid,',',dim,',2)=', mask_loop(mid,dim,2),    &
    736                      ' exceeds dz_stretch_level=',dz_stretch_level,            &
     742                     ' exceeds dz_stretch_level=',dz_stretch_level_start(1),   &
    737743                     '.&Vertical mask locations will not ',                    &
    738744                     'match the desired heights within the stretching ',       &
Note: See TracChangeset for help on using the changeset viewer.