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

    r2801 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 2801 2018-02-14 16:01:55Z thiele
    2730! Introduce particle transfer in nested models.
    2831!
     
    123126    SUBROUTINE lpm_sort_in_subboxes
    124127
    125        USE cpulog,                                                              &
     128       USE cpulog,                                                             &
    126129          ONLY:  cpu_log, log_point_s
    127130
    128        USE indices,                                                             &
     131       USE indices,                                                            &
    129132          ONLY:  nxl, nxr, nys, nyn, nzb, nzt
    130133
    131134       USE kinds
    132135
    133        USE control_parameters,                                                  &
    134           ONLY: dz
    135        
    136        USE grid_variables,                                                      &
     136       USE grid_variables,                                                     &
    137137          ONLY: dx,dy,ddx, ddy
    138138           
    139        USE arrays_3d,                                                           &
     139       USE arrays_3d,                                                          &
    140140          ONLY:  zu
     141
    141142       IMPLICIT NONE
    142143
     
    146147       INTEGER(iwp) ::  j  !<
    147148       INTEGER(iwp) ::  jp !<
    148        INTEGER(iwp) ::  k  !<
    149149       INTEGER(iwp) ::  kp !<
    150150       INTEGER(iwp) ::  m  !<
Note: See TracChangeset for help on using the changeset viewer.