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

    r3215 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3215 2018-08-29 09:58:59Z suehring
    2730! - Separate input of soil properties from input of atmospheric data. This
    2831!   enables input of soil properties also in child domains without any
     
    654657
    655658       USE control_parameters,                                                 &
    656            ONLY:  land_surface, message_string, topo_no_distinct, urban_surface
     659           ONLY:  topo_no_distinct
    657660
    658661       IMPLICIT NONE
    659 
    660        LOGICAL ::  check_nest  !< flag indicating whether a check passed or not
    661662
    662663#if defined ( __netcdf )
     
    688689
    689690       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
    690        INTEGER(iwp) ::  ii       !< running index for IO blocks
    691691
    692692       IF ( .NOT. input_pids_static )  RETURN
     
    757757
    758758       USE control_parameters,                                                 &
    759            ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, message_string,          &
    760                   plant_canopy, urban_surface
     759           ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, plant_canopy,            &
     760                  urban_surface
    761761
    762762       USE indices,                                                            &
     
    17881788
    17891789       USE indices,                                                            &
    1790            ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb, nzt
     1790           ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
    17911791
    17921792
     
    18001800       INTEGER(iwp) ::  id_topo       !< NetCDF id of topograhy input file
    18011801       INTEGER(iwp) ::  j             !< running index along y-direction
    1802        INTEGER(iwp) ::  k             !< running index along z-direction
    18031802       INTEGER(iwp) ::  num_vars      !< number of variables in netcdf input file
    18041803       INTEGER(iwp) ::  skip_n_rows   !< counting variable to skip rows while reading topography file
     
    20792078
    20802079       USE control_parameters,                                                 &
    2081            ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, land_surface, message_string,&
    2082                   nesting_offline, neutral, surface_pressure
     2080           ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, message_string, neutral
    20832081
    20842082       USE indices,                                                            &
     
    20912089       LOGICAL      ::  dynamic_3d = .TRUE. !< flag indicating that 3D data is read from dynamic file
    20922090       
    2093        INTEGER(iwp) ::  i          !< running index along x-direction
    20942091       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
    2095        INTEGER(iwp) ::  j          !< running index along y-direction
    2096        INTEGER(iwp) ::  k          !< running index along z-direction
    20972092       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    20982093
     
    25542549    SUBROUTINE netcdf_data_input_init_lsm
    25552550
    2556        USE arrays_3d,                                                          &
    2557            ONLY:  q, pt, u, v, w, zu, zw
    2558 
    25592551       USE control_parameters,                                                 &
    2560            ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, land_surface, message_string,&
    2561                   nesting_offline, neutral, surface_pressure
     2552           ONLY:  message_string
    25622553
    25632554       USE indices,                                                            &
    2564            ONLY:  nx, nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nz, nzt
     2555           ONLY:  nx, nxl, nxr, ny, nyn, nys
    25652556
    25662557       IMPLICIT NONE
     
    26992690           ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,              &
    27002691                  bc_dirichlet_s, bc_lr_cyc, bc_ns_cyc, humidity,              &
    2701                   message_string, neutral, nesting_offline,                    &
    2702                   time_since_reference_point
     2692                  neutral, nesting_offline, time_since_reference_point
    27032693
    27042694       USE indices,                                                            &
     
    27072697       IMPLICIT NONE
    27082698       
    2709        INTEGER(iwp) ::  i          !< running index along x-direction
    27102699       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
    2711        INTEGER(iwp) ::  j          !< running index along y-direction
    2712        INTEGER(iwp) ::  k          !< running index along z-direction
    27132700       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
    27142701       INTEGER(iwp) ::  t          !< running index time dimension
    2715 
    2716        REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
    27172702
    27182703       nest_offl%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic )
     
    35623547       IMPLICIT NONE
    35633548
    3564        LOGICAL      ::  top     !< flag indicating extrapolation at model top
    3565 
    35663549       INTEGER(iwp) ::  k       !< running index z-direction file
    35673550       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
    35683551       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    35693552       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3570        INTEGER(iwp) ::  nz_file !< number of vertical levels on file
    3571 
    35723553
    35733554       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
     
    36313612       IMPLICIT NONE
    36323613
    3633        INTEGER(iwp) ::  i        !< running index x-direction
    3634        INTEGER(iwp) ::  j        !< running index y-direction
    36353614       INTEGER(iwp) ::  k        !< running index z-direction file
    36363615       INTEGER(iwp) ::  kk       !< running index z-direction stretched model grid
     
    36903669       IMPLICIT NONE
    36913670
    3692        LOGICAL      ::  top     !< flag indicating extrapolation at model top
    3693 
    36943671       INTEGER(iwp) ::  i       !< running index x- or y -direction
    36953672       INTEGER(iwp) ::  il      !< lower index bound along x- or y-direction
     
    36993676       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    37003677       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3701        INTEGER(iwp) ::  nz_file !< number of vertical levels on file
    3702 
    37033678
    37043679       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
     
    37713746       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
    37723747       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
    3773        INTEGER(iwp) ::  nz_file !< number of vertical levels on file
    37743748
    37753749       REAL(wp), DIMENSION(:) ::  z_grid                      !< grid levels on numeric grid
     
    38873861       CHARACTER (LEN=*), INTENT(IN) ::  filename  !< filename
    38883862       INTEGER(iwp), INTENT(INOUT)   ::  id        !< file id
    3889        LOGICAL                       ::  file_open = .FALSE.
    38903863
    38913864#if defined( __netcdf4_parallel )
Note: See TracChangeset for help on using the changeset viewer.