Ignore:
Timestamp:
Mar 4, 2019 12:40:20 PM (6 years ago)
Author:
gronemeier
Message:

removed unused variables

File:
1 edited

Legend:

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

    r3724 r3775  
    2525! -----------------
    2626! $Id$
     27! removed unused variables
     28!
     29! 3724 2019-02-06 16:28:23Z kanani
    2730! Correct double-used log_point_s units
    2831!
     
    12281231
    12291232    USE control_parameters,                                                    &
    1230         ONLY:  bc_lr_cyc, bc_ns_cyc, f, message_string, wall_adjustment_factor
     1233        ONLY:  f, message_string, wall_adjustment_factor
    12311234
    12321235    USE grid_variables,                                                        &
     
    12621265
    12631266    INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE :: vicinity !< contains topography information of the vicinity of (i/j/k)
    1264 
    1265     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE :: wall_flags_dummy    !< dummy array required for MPI_ALLREDUCE command
    12661267
    12671268    REAL(wp) :: radius           !< search radius in meter
     
    19271928 SUBROUTINE tcm_prognostic_equations
    19281929
    1929     USE arrays_3d,                                                             &
    1930         ONLY:  ddzu
    1931 
    19321930    USE control_parameters,                                                    &
    1933         ONLY:  f, scalar_advec, tsc
    1934 
    1935     USE surface_mod,                                                           &
    1936         ONLY :  surf_def_h
     1931        ONLY:  scalar_advec, tsc
    19371932
    19381933    IMPLICIT NONE
     
    19411936    INTEGER(iwp) ::  j       !< loop index
    19421937    INTEGER(iwp) ::  k       !< loop index
    1943     INTEGER(iwp) ::  m       !< loop index
    1944     INTEGER(iwp) ::  surf_e  !< end index of surface elements at given i-j position
    1945     INTEGER(iwp) ::  surf_s  !< start index of surface elements at given i-j position
    19461938
    19471939    REAL(wp)     ::  sbt     !< wheighting factor for sub-time step
     
    36773669 SUBROUTINE diffusion_e( var, var_reference )
    36783670
     3671#ifdef _OPENACC
    36793672    USE arrays_3d,                                                             &
    36803673        ONLY:  ddzu, dd2zu, ddzw, drho_air, rho_air_zw
     
    36833676        ONLY:  atmos_ocean_sign, use_single_reference_value,                   &
    36843677               wall_adjustment, wall_adjustment_factor
    3685 
     3678#else
     3679    USE arrays_3d,                                                             &
     3680        ONLY:  ddzu, ddzw, drho_air, rho_air_zw
     3681#endif
    36863682    USE grid_variables,                                                        &
    36873683        ONLY:  ddx2, ddy2
     
    44334429 SUBROUTINE tcm_diffusivities_default( var, var_reference )
    44344430 
     4431#ifdef _OPENACC
    44354432    USE arrays_3d,                                                             &
    44364433        ONLY:  dd2zu
     
    44394436        ONLY:  atmos_ocean_sign, use_single_reference_value,                   &
    44404437               wall_adjustment, wall_adjustment_factor
     4438#endif
    44414439
    44424440    USE statistics,                                                            &
Note: See TracChangeset for help on using the changeset viewer.