Ignore:
Timestamp:
Sep 12, 2018 3:02:00 PM (6 years ago)
Author:
raasch
Message:

various changes to avoid compiler warnings (mainly removal of unused variables)

File:
1 edited

Legend:

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

    r3120 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3120 2018-07-11 18:30:57Z gronemeier
    2730! Put ABS( km ) in computation of time step according to the diffusion criterion
    2831!
     
    188191    REAL(wp) ::  kh_max            !< maximum of Kh in entire domain
    189192    REAL(wp) ::  u_gtrans_l        !<
    190     REAL(wp) ::  u_max_l           !<
    191     REAL(wp) ::  u_min_l           !<
    192     REAL(wp) ::  value             !<
    193193    REAL(wp) ::  v_gtrans_l        !<
    194     REAL(wp) ::  v_max_l           !<
    195     REAL(wp) ::  v_min_l           !<
    196     REAL(wp) ::  w_max_l           !<
    197     REAL(wp) ::  w_min_l           !<
    198194 
    199195    REAL(wp), DIMENSION(2)         ::  uv_gtrans   !<
     
    313309       ENDDO
    314310
    315        !$OMP PARALLEL private(i,j,k,value) reduction(MIN: dt_diff_l)
     311       !$OMP PARALLEL private(i,j,k) reduction(MIN: dt_diff_l)
    316312       !$OMP DO
    317313       DO  i = nxl, nxr
Note: See TracChangeset for help on using the changeset viewer.