Ignore:
Timestamp:
Mar 7, 2019 11:40:09 AM (5 years ago)
Author:
banzhafs
Message:

Removed unused variables from chem_emissions_mod

File:
1 edited

Legend:

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

    r3772 r3788  
    2727! -----------------
    2828! $Id$
     29! Removed unused variables from chem_emissions_mod
     30!
     31!3772 2019-02-28 15:51:57Z suehring
    2932! - In case of parametrized emissions, assure that emissions are only on natural
    3033!   surfaces (i.e. streets) and not on urban surfaces.
    3134! - some unnecessary if clauses removed
    32 ! 
    33 ! 3685 2019-01-21 01:02:11Z knoop
     35!
     36!3685 2019 -01-21 01:02:11Z knoop
    3437! Some interface calls moved to module_interface + cleanup
    3538!
     
    204207    IMPLICIT NONE
    205208
    206     INTEGER(iwp) ::  tmp
    207 
    208209    TYPE(chem_emis_att_type) ::  emt
    209210
     
    703704 SUBROUTINE chem_emissions_init
    704705
    705     USE surface_mod,                                                           &
    706         ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
    707 
    708706    USE netcdf_data_input_mod,                                                 &
    709707        ONLY:  chem_emis, chem_emis_att
     
    711709    IMPLICIT NONE
    712710 
    713     CHARACTER (LEN=80)          ::  units                                           !< units of inputs
    714 
    715711    INTEGER(iwp)                :: ispec                                            !< running index
    716712
     
    814810
    815811 SUBROUTINE chem_emissions_setup( emt_att, emt, nspec_out )
    816 
    817    USE arrays_3d,                                                    &
    818        ONLY:  dzw
    819    USE grid_variables,                                               &
    820        ONLY: dx, dy
    821    USE indices,                                                      &
    822        ONLY: nnx, nny, nnz
     812 
    823813   USE surface_mod,                                                  &
    824814       ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     
    839829    INTEGER,INTENT(IN) ::  nspec_out                                            !< Output of matching routine with number
    840830                                                                                !< of matched species
    841 
    842     CHARACTER(LEN=80) ::  units                                                 !< Units of the emission data
    843831
    844832    INTEGER(iwp) ::  i                                                          !< running index for grid in x-direction
     
    851839    INTEGER(iwp) ::  i_pm_comp                                                  !< index for number of PM components
    852840    INTEGER(iwp) ::  ivoc                                                       !< Index for number of VOCs
    853     INTEGER(iwp) ::  time_index                                                 !< Index for time
    854841
    855842    REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::  delta_emis                       
Note: See TracChangeset for help on using the changeset viewer.