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

    r3215 r3241  
    298298                                                                                 
    299299    USE control_parameters,                                                    & 
    300         ONLY:  air_chemistry, bc_radiation_l, bc_radiation_n, bc_radiation_r,  &
    301                bc_radiation_s               
     300        ONLY:  bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s
     301
    302302    USE indices,                                                               & 
    303         ONLY:  nxl, nxr,  nxlg, nxrg, nyng, nysg, nzt                             
     303        ONLY:  nxl, nxr, nzt
    304304                                                                                 
    305 !    USE prognostic_equations_mod,                                             &
    306 
    307305    USE arrays_3d,                                                             &     
    308306        ONLY:  dzu                                               
     307
    309308    USE surface_mod,                                                           &
    310309        ONLY:  bc_h                                                           
     
    318317    INTEGER(iwp) ::  m                                                            !< running index surface elements.
    319318    INTEGER(iwp) ::  lsp                                                          !< running index for chem spcs.
    320     INTEGER(iwp) ::  lph                                                          !< running index for photolysis frequencies
    321319
    322320
     
    469467    INTEGER ::  lsp_pr     !< running index for number of species in cs_names, cs_profiles etc
    470468    INTEGER ::  lpr_lev    !< running index for profile level for each chem spcs.
    471     INTEGER ::  npr_lev    !< the next available profile lev
     469!    INTEGER ::  npr_lev    !< the next available profile lev
    472470
    473471!-----------------
     
    548546!------------------------------------------------------------------------------!
    549547   SUBROUTINE chem_init
    550 
    551 
    552       USE control_parameters,                                                  &
    553          ONLY: message_string, io_blocks, io_group, turbulent_inflow
    554        
    555       USE arrays_3d,                                                           &
    556           ONLY: mean_inflow_profiles
    557548
    558549      USE pegrid
     
    917908      INTEGER(iwp) ::  lsp                                                          !< running index for chem spcs.
    918909      INTEGER(iwp) ::  lph                                                          !< running index for photolysis frequencies
    919       INTEGER                  :: k,m,istatf                                       
     910      INTEGER                  :: istatf
    920911      INTEGER,dimension(20)    :: istatus
    921912      REAL(kind=wp),dimension(nzb+1:nzt,nspec)                :: tmp_conc           
     
    926917     REAL(wp)                         ::  conv                                !< conversion factor
    927918     REAL(wp), PARAMETER              ::  ppm2fr  = 1.0e-6_wp                 !< Conversion factor ppm to fraction
    928      REAL(wp), PARAMETER              ::  pref_i  = 1._wp / 100000.0_wp       !< inverse reference pressure (1/Pa)
    929919     REAL(wp), PARAMETER              ::  t_std   = 273.15_wp                 !< standard pressure (Pa)
    930920     REAL(wp), PARAMETER              ::  p_std   = 101325.0_wp               !< standard pressure (Pa)
    931      REAL(wp), PARAMETER              ::  r_cp    = 0.286_wp                  !< R / cp (exponent for potential temperature)
    932921     REAL(wp), PARAMETER              ::  vmolcm  = 22.414e3_wp               !< Mole volume (22.414 l) in cm^{-3}
    933922     REAL(wp), PARAMETER              ::  xna     = 6.022e23_wp               !< Avogadro number (molecules/mol)
     
    10681057   SUBROUTINE chem_check_data_output( var, unit, i, ilen, k )
    10691058
    1070 
    1071       USE control_parameters,                                                 &
    1072          ONLY: data_output, message_string
    1073 
    10741059      IMPLICIT NONE
    10751060
     
    10771062      CHARACTER (LEN=*) ::  var      !<
    10781063
    1079       INTEGER(iwp) :: i, lsp
    1080       INTEGER(iwp) :: ilen
    1081       INTEGER(iwp) :: k
     1064      INTEGER(iwp) ::  i, ilen, k, lsp
    10821065
    10831066      CHARACTER(len=16)    ::  spec_name
     
    12781261    INTEGER(iwp) ::  m                  !< running index surface type
    12791262    INTEGER(iwp) :: lsp                 !< running index for chem spcs
    1280     INTEGER(iwp) :: lsp_2               !< it looks like redundent .. will be delted ..bK
    12811263 
    12821264    IF ( mode == 'allocate' )  THEN
    12831265       DO lsp = 1, nspec
    12841266          IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN
    1285 !                   lsp_2 = lsp
    12861267             chem_species(lsp)%conc_av = 0.0_wp
    1287              
    12881268          ENDIF
    12891269       ENDDO
     
    12931273       DO lsp = 1, nspec
    12941274          IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN
    1295 !                   lsp_2 = lsp
    12961275             DO  i = nxlg, nxrg
    12971276                DO  j = nysg, nyng
     
    13361315       DO lsp = 1, nspec
    13371316          IF (TRIM(variable(4:)) == TRIM(chem_species(lsp)%name)) THEN
    1338 !                   lsp_2 = lsp
    13391317             DO  i = nxlg, nxrg
    13401318                DO  j = nysg, nyng
Note: See TracChangeset for help on using the changeset viewer.