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

    r3183 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed, shortest_distance has wp now
     28!
     29! 3183 2018-07-27 14:25:55Z suehring
    2730! Rename variables and remove unused variable from USE statement
    2831!
     
    200203    REAL(wp) ::  c_1                !< model constant for RANS mode
    201204    REAL(wp) ::  c_2                !< model constant for RANS mode
    202     REAL(wp) ::  c_3                !< model constant for RANS mode
     205!    REAL(wp) ::  c_3                !< model constant for RANS mode
    203206    REAL(wp) ::  c_4                !< model constant for RANS mode
    204207    REAL(wp) ::  l_max              !< maximum length scale for Blackadar mixing length
    205208    REAL(wp) ::  dsig_e = 1.0_wp    !< factor to calculate Ke from Km (1/sigma_e)
    206209    REAL(wp) ::  dsig_diss = 1.0_wp !< factor to calculate K_diss from Km (1/sigma_diss)
    207     INTEGER(iwp) ::  surf_e         !< end index of surface elements at given i-j position
    208     INTEGER(iwp) ::  surf_s         !< start index of surface elements at given i-j position
    209210
    210211    REAL(wp), DIMENSION(0:4) :: rans_const_c = &       !< model constants for RANS mode (namelist param)
     
    382383
    383384    USE control_parameters,                                                    &
    384         ONLY:  message_string, neutral, turbulent_inflow, turbulent_outflow
     385        ONLY:  message_string, turbulent_inflow, turbulent_outflow
    385386
    386387    IMPLICIT NONE
     
    459460!> Check data output.
    460461!------------------------------------------------------------------------------!
    461  SUBROUTINE tcm_check_data_output( var, unit, i, ilen, k )
     462 SUBROUTINE tcm_check_data_output( var, unit )
    462463 
    463     USE control_parameters,                                                    &
    464         ONLY:  data_output, message_string
    465 
    466464    IMPLICIT NONE
    467465
     
    469467    CHARACTER (LEN=*) ::  var      !< name of output variable
    470468
    471     INTEGER(iwp) ::  i      !< index of var in data_output
    472     INTEGER(iwp) ::  ilen   !< length of var string
    473     INTEGER(iwp) ::  k      !< flag if var contains one of '_xy', '_xz' or '_yz'
    474469
    475470    SELECT CASE ( TRIM( var ) )
     
    697692!------------------------------------------------------------------------------!
    698693 SUBROUTINE tcm_data_output_2d( av, variable, found, grid, mode, local_pf,     &
    699                                 two_d, nzb_do, nzt_do )
     694                                nzb_do, nzt_do )
    700695 
    701696    USE averaging,                                                             &
     
    717712
    718713    LOGICAL ::  found   !< flag if output variable is found
    719     LOGICAL ::  two_d   !< flag parameter that indicates 2D variables (horizontal cross sections)
    720714    LOGICAL ::  resorted  !< flag if output is already resorted
    721715
     
    10521046
    10531047    USE control_parameters,                                                    &
    1054         ONLY:  bc_dirichlet_l, complex_terrain, dissipation_1d, topography
     1048        ONLY:  bc_dirichlet_l, complex_terrain, topography
    10551049
    10561050    USE model_1d_mod,                                                          &
    1057         ONLY:  diss1d, e1d, kh1d, km1d, l1d
     1051        ONLY:  e1d, kh1d, km1d
    10581052
    10591053    USE surface_mod,                                                           &
     
    13391333    INTEGER(iwp) :: ii             !< index variable along x
    13401334    INTEGER(iwp) :: j              !< index variable along y
    1341     INTEGER(iwp) :: jj             !< index variable along y
    13421335    INTEGER(iwp) :: k              !< index variable along z
    13431336    INTEGER(iwp) :: k_max_topo = 0 !< index of maximum topography height
     
    18041797!>   and debug options for the compiler. This should be fixed
    18051798!------------------------------------------------------------------------------!
    1806     REAL FUNCTION shortest_distance( array, orientation, pos_i )
     1799    REAL(wp) FUNCTION shortest_distance( array, orientation, pos_i )
    18071800
    18081801       IMPLICIT NONE
     
    20892082
    20902083    USE surface_mod,                                                           &
    2091         ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
    2092                 surf_usm_v
     2084        ONLY :  surf_def_h
    20932085
    20942086    IMPLICIT NONE
     
    23712363
    23722364    USE arrays_3d,                                                             &
    2373         ONLY:  ddzu, diss_l_diss, diss_l_e, diss_s_diss, diss_s_e,             &
    2374                flux_l_diss, flux_l_e, flux_s_diss, flux_s_e,&
    2375                u_p,v_p,w_p
     2365        ONLY:  diss_l_diss, diss_l_e, diss_s_diss, diss_s_e, flux_l_diss,      &
     2366               flux_l_e, flux_s_diss, flux_s_e
    23762367
    23772368    USE control_parameters,                                                    &
    2378         ONLY:  f, tsc
    2379 
    2380     USE grid_variables,                                                        &
    2381         ONLY:  dx, dy
    2382 
    2383     USE surface_mod,                                                           &
    2384         ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
    2385                 surf_usm_v
    2386 
    2387     use indices, only: nx, ny
     2369        ONLY:  tsc
    23882370
    23892371    IMPLICIT NONE
     
    23932375    INTEGER(iwp) ::  j       !< loop index y direction
    23942376    INTEGER(iwp) ::  k       !< loop index z direction
    2395     INTEGER(iwp) ::  l       !< loop index
    2396     INTEGER(iwp) ::  m       !< loop index
    2397     INTEGER(iwp) ::  surf_e  !< end index of surface elements at given i-j position
    2398     INTEGER(iwp) ::  surf_s  !< start index of surface elements at given i-j position
    23992377    INTEGER(iwp) ::  tn      !< task number of openmp task
    24002378
    2401     INTEGER(iwp) :: pis = 32 !< debug variable, print from i=pis                !> @todo remove later
    2402     INTEGER(iwp) :: pie = 32 !< debug variable, print until i=pie               !> @todo remove later
    2403     INTEGER(iwp) :: pjs = 26 !< debug variable, print from j=pjs                !> @todo remove later
    2404     INTEGER(iwp) :: pje = 26 !< debug variable, print until j=pje               !> @todo remove later
    2405     INTEGER(iwp) :: pkb = 1  !< debug variable, print from k=pkb                !> @todo remove later
    2406     INTEGER(iwp) :: pkt = 7  !< debug variable, print until k=pkt               !> @todo remove later
     2379!    INTEGER(iwp) :: pis = 32 !< debug variable, print from i=pis                !> @todo remove later
     2380!    INTEGER(iwp) :: pie = 32 !< debug variable, print until i=pie               !> @todo remove later
     2381!    INTEGER(iwp) :: pjs = 26 !< debug variable, print from j=pjs                !> @todo remove later
     2382!    INTEGER(iwp) :: pje = 26 !< debug variable, print until j=pje               !> @todo remove later
     2383!    INTEGER(iwp) :: pkb = 1  !< debug variable, print from k=pkb                !> @todo remove later
     2384!    INTEGER(iwp) :: pkt = 7  !< debug variable, print until k=pkt               !> @todo remove later
    24072385
    24082386    REAL(wp), DIMENSION(nzb:nzt+1) :: dum_adv   !< debug variable               !> @todo remove later
     
    24102388    REAL(wp), DIMENSION(nzb:nzt+1) :: dum_dif   !< debug variable               !> @todo remove later
    24112389
    2412 5555 FORMAT(A,7(1X,E12.5))   !> @todo remove later
     2390!5555 FORMAT(A,7(1X,E12.5))   !> @todo remove later
    24132391
    24142392!
     
    48124790    INTEGER(iwp) ::  j                   !< loop index
    48134791    INTEGER(iwp) ::  k                   !< loop index
    4814     INTEGER(iwp) ::  omp_get_thread_num  !< opemmp function to get thread number
     4792!$  INTEGER(iwp) ::  omp_get_thread_num  !< opemmp function to get thread number
    48154793    INTEGER(iwp) ::  sr                  !< statistic region
    48164794    INTEGER(iwp) ::  tn                  !< thread number
     
    49704948    REAL(wp)     ::  vc(-1:1,-1:1)  !< v on grid center
    49714949    REAL(wp)     ::  wc(-1:1,-1:1)  !< w on grid center
    4972     REAL(wp)     ::  u2(-1:1,-1:1)  !< u2 on grid center
    4973     REAL(wp)     ::  v2(-1:1,-1:1)  !< v2 on grid center
    4974     REAL(wp)     ::  w2(-1:1,-1:1)  !< w2 on grid center
    4975     REAL(wp)     ::  uv(-1:1,-1:1)  !< u*v on grid center
    4976     REAL(wp)     ::  uw(-1:1,-1:1)  !< u*w on grid center
    4977     REAL(wp)     ::  vw(-1:1,-1:1)  !< v*w on grid center
     4950!    REAL(wp)     ::  u2(-1:1,-1:1)  !< u2 on grid center
     4951!    REAL(wp)     ::  v2(-1:1,-1:1)  !< v2 on grid center
     4952!    REAL(wp)     ::  w2(-1:1,-1:1)  !< w2 on grid center
     4953!    REAL(wp)     ::  uv(-1:1,-1:1)  !< u*v on grid center
     4954!    REAL(wp)     ::  uw(-1:1,-1:1)  !< u*w on grid center
     4955!    REAL(wp)     ::  vw(-1:1,-1:1)  !< v*w on grid center
    49784956
    49794957    REAL(wp)     ::  ut(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !< test filtered u
     
    52295207    IMPLICIT NONE
    52305208
     5209
     5210#if defined( __nopointer )
    52315211    INTEGER(iwp) ::  i      !< loop index x direction
    52325212    INTEGER(iwp) ::  j      !< loop index y direction
    52335213    INTEGER(iwp) ::  k      !< loop index z direction
     5214#endif
    52345215    INTEGER, INTENT(IN) ::  mod_count  !< flag defining where pointers point to
    52355216
Note: See TracChangeset for help on using the changeset viewer.