Ignore:
Timestamp:
Dec 10, 2018 7:05:46 AM (6 years ago)
Author:
raasch
Message:

unused variables removed, abort renamed inifor_abort to avoid intrinsic problem in Fortran

File:
1 edited

Legend:

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

    r3560 r3614  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3560 2018-11-23 09:20:21Z raasch
    2730! Some formatting adjustment
    2831!
     
    12671270
    12681271       USE chem_modules,                                       &
    1269            ONLY:  do_emis, mode_emis, time_fac_type,           &
    1270                   surface_csflux_name
     1272           ONLY:  mode_emis, time_fac_type, surface_csflux_name
    12711273
    12721274       USE control_parameters,                                 &
     
    12741276
    12751277       USE indices,                                            &
    1276            ONLY:  nz, nx, ny, nxl, nxr, nys, nyn, nzb, nzt
     1278           ONLY:  nx, ny, nxl, nxr, nys, nyn
    12771279
    12781280       IMPLICIT NONE
     
    12811283       TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)             :: emt
    12821284   
    1283        CHARACTER (LEN=80)                               :: units=''              !< units of chemistry inputs
    1284  
    12851285       INTEGER(iwp)                                     :: ispec                 !< index for number of emission species in input
    12861286
    1287        INTEGER(iwp), ALLOCATABLE, DIMENSION(:)          :: dum_var               !< value of variable read from netcdf input
    1288        INTEGER(iwp)                                     :: errno                 !< error number NF90_???? function
    1289        INTEGER(iwp)                                     :: id_var                !< variable id
    1290 !       INTEGER(iwp)                                     :: id_emis               !< NetCDF id of input file
    12911287       INTEGER(iwp)                                     :: num_vars              !< number of variables in netcdf input file
    1292        INTEGER(iwp)                                     :: len_dims,len_dims_2   !< Length of dimensions
    1293 
    1294        INTEGER(iwp)                                     :: max_string_length=25  !< Variable for the maximum length of a string
    1295  
    1296        CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE    :: var_names             !< Name of Variables
     1288       INTEGER(iwp)                                     :: len_dims              !< Length of dimension
    12971289
    12981290       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)          :: dum_var_3d            !< variable for storing temporary data of 3-dimensional
     
    15621554
    15631555       USE control_parameters,                                                 &
    1564            ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, plant_canopy,            &
    1565                   urban_surface
     1556           ONLY:  land_surface, plant_canopy, urban_surface
    15661557
    15671558       USE indices,                                                            &
    1568            ONLY:  nbgp, nx, nxl, nxr,ny, nyn, nys
     1559           ONLY:  nbgp, nxl, nxr, nyn, nys
    15691560
    15701561
     
    24062397
    24072398       USE control_parameters,                                                 &
    2408            ONLY:  bc_lr_cyc, bc_ns_cyc, message_string, topography
     2399           ONLY:  message_string, topography
    24092400
    24102401       USE indices,                                                            &
    2411            ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
     2402           ONLY:  nbgp, nxl, nxr, ny, nyn, nys, nzb
    24122403
    24132404
Note: See TracChangeset for help on using the changeset viewer.