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

    r3183 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3183 2018-07-27 14:25:55Z suehring
    2730! Rename variables in mesoscale-offline nesting mode
    2831!
     
    305308
    306309       USE arrays_3d,                                                          &
    307            ONLY:  f1_mg, f2_mg, f3_mg, rho_air_mg
     310           ONLY:  rho_air_mg
    308311
    309312       USE control_parameters,                                                 &
     
    725728
    726729       USE arrays_3d,                                                          &
    727            ONLY:  f1_mg, f2_mg, f3_mg, rho_air_mg
     730           ONLY:  rho_air_mg
    728731
    729732       USE control_parameters,                                                 &
     
    10331036
    10341037
    1035        USE control_parameters,                                                 &
    1036            ONLY:  grid_level
    1037 
    10381038       USE indices,                                                            &
    10391039           ONLY:  nxl_mg, nxr_mg, nys_mg, nyn_mg, nzb, nzt_mg
     
    11481148    SUBROUTINE sort_k_to_even_odd_blocks_int( i_mg , glevel )
    11491149
    1150 
    1151        USE control_parameters,                                                 &
    1152            ONLY:  grid_level
    11531150
    11541151       USE indices,                                                            &
     
    14091406       USE control_parameters,                                                 &
    14101407           ONLY:  bc_lr_dirrad, bc_lr_raddir, bc_ns_dirrad, bc_ns_raddir,      &
    1411                   child_domain, gamma_mg, grid_level_count, ibc_p_b, ibc_p_t,  &
    1412                   maximum_grid_level,  mg_switch_to_pe0_level,                 &
    1413                   mg_switch_to_pe0, ngsrb
     1408                  child_domain, gamma_mg, grid_level_count, maximum_grid_level,&
     1409                  mg_switch_to_pe0_level, mg_switch_to_pe0, ngsrb
    14141410
    14151411       USE indices,                                                            &
     
    17711767
    17721768       USE indices,                                                            &
    1773            ONLY:  nxl_mg, nxr_mg, nys_mg, nyn_mg, nzb, nzt_mg
     1769           ONLY:  nzb, nzt_mg
    17741770
    17751771       IMPLICIT NONE
     
    18221818!> "red" or "black" data points.
    18231819!------------------------------------------------------------------------------!
    1824      SUBROUTINE special_exchange_horiz ( p_mg, color )
     1820     SUBROUTINE special_exchange_horiz( p_mg, color )
    18251821
    18261822
    18271823       USE control_parameters,                                                 &
    1828            ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t,          &
    1829                   maximum_grid_level,                                          &
    1830                   mg_switch_to_pe0_level, synchronous_exchange
     1824           ONLY:  grid_level, mg_switch_to_pe0_level, synchronous_exchange
    18311825
    18321826       USE indices,                                                            &
    1833            ONLY:  mg_loc_ind, nxl, nxl_mg, nxr, nxr_mg, nys, nys_mg, nyn,      &
     1827           ONLY:  nxl, nxl_mg, nxr, nxr_mg, nys, nys_mg, nyn,      &
    18341828                  nyn_mg, nzb, nzt, nzt_mg
    18351829
Note: See TracChangeset for help on using the changeset viewer.