Changeset 3787 for palm


Ignore:
Timestamp:
Mar 7, 2019 8:43:54 AM (5 years ago)
Author:
raasch
Message:

unused variables removed

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r3780 r3787  
    2626! -----------------
    2727! $Id$
     28! unused variables removed
     29!
     30! 3780 2019-03-05 11:19:45Z forkel
    2831! unused variable for file index removed from rrd-subroutines parameter list
    2932!
     
    297300                                !< if particle water is advected)
    298301    REAL(wp) ::  act_coeff = 1.0E-7_wp     !< Activation coefficient
    299     REAL(wp) ::  aerosol_source = 0.0_wp   !< Constant aerosol flux (#/(m3*s))
    300302    REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::  emission_mass_fracs  !< array for
    301303                                    !< aerosol composition per emission category
     
    20422044    IMPLICIT NONE
    20432045   
    2044     CHARACTER (LEN=20) :: field_char   !<
    20452046    INTEGER(iwp) ::  b  !<   
    20462047    INTEGER(iwp) ::  c  !<
     
    31113112   
    31123113    INTEGER(iwp) ::  b      !< loop index
    3113     INTEGER(iwp) ::  c      !< loop index
    31143114    REAL(wp) ::  avis       !< molecular viscocity of air (kg/(m*s))
    31153115    REAL(wp), PARAMETER ::  c_A = 1.249_wp !< Constants A, B and C for
     
    31973197   
    31983198    INTEGER(iwp) ::  c      !< loop index
    3199     REAL(wp), PARAMETER ::  c_A = 1.249_wp !< Constants A, B and C for
    3200     REAL(wp), PARAMETER ::  c_B = 0.42_wp  !< calculating  the Cunningham 
    3201     REAL(wp), PARAMETER ::  c_C = 0.87_wp  !< slip-flow correction (Cc) 
    3202                                            !< according to Jacobson (2005),
    3203                                            !< Eq. 15.30
     3199
    32043200    REAL(wp) ::  alpha       !< parameter, Table 3 in Zhang et al. (2001) 
    32053201    REAL(wp) ::  depo        !< deposition efficiency
     
    34503446    REAL(wp), INTENT(in) ::  visc    !< molecular viscosity of air (kg/(m*s))
    34513447   
    3452     REAL(wp), PARAMETER ::  rhoa_ref = 1.225_wp ! reference air density (kg/m3)
    34533448!
    34543449!-- Stokes law with Cunningham slip correction factor
     
    55715566    REAL(wp) ::  zcgnh3eqae(nbins)  !< Equilibrium gas concentration: NH3
    55725567    REAL(wp) ::  zcgno3eqae(nbins)  !< Equilibrium gas concentration: HNO3
    5573     REAL(wp) ::  zcgwaeqae(nbins)   !< Equilibrium gas concentration: H2O
    55745568    REAL(wp) ::  zcnh3c             !< Current NH3 gas concentration
    55755569    REAL(wp) ::  zcnh3int           !< Intermediate NH3 gas concentration
     
    56705664!
    56715665!-- NH4/HNO3 saturation ratios for aerosols
    5672     CALL SVsat( ptemp, paero, zacno3ae, zacnh3ae, zacnh4hso2ae, zachhso4ae,    &
    5673                 zcgno3eqae, zcno3cae, zcnh3cae, zkelno3ae, zkelnh3ae,          &
    5674                 zsathno3ae, zsatnh3ae, zmolsae )
     5666    CALL SVsat( ptemp, paero, zacno3ae, zacnh4hso2ae, zachhso4ae, zcgno3eqae,  &
     5667                zcno3cae, zcnh3cae, zkelno3ae, zkelnh3ae, zsathno3ae, zsatnh3ae )
    56755668!   
    56765669!-- Intermediate concentrations   
     
    58085801!> Calculate saturation ratios of NH4 and HNO3 for aerosols
    58095802!------------------------------------------------------------------------------!
    5810  SUBROUTINE SVsat( ptemp, ppart, pachno3, pacnh3, pacnh4hso2, pachhso4,        &
    5811                    pchno3eq, pchno3, pcnh3, pkelhno3, pkelnh3, psathno3,       &
    5812                    psatnh3, pmols )
     5803 SUBROUTINE SVsat( ptemp, ppart, pachno3, pacnh4hso2, pachhso4, pchno3eq,      &
     5804                   pchno3, pcnh3, pkelhno3, pkelnh3, psathno3, psatnh3 )
    58135805
    58145806    IMPLICIT NONE
     
    58195811!-- Activity coefficients
    58205812    REAL(wp), INTENT(in) ::  pachhso4(nbins)   !<
    5821     REAL(wp), INTENT(in) ::  pacnh3(nbins)     !<
    58225813    REAL(wp), INTENT(in) ::  pacnh4hso2(nbins) !<
    58235814    REAL(wp), INTENT(in) ::  pachno3(nbins)    !<
     
    58305821    REAL(wp), INTENT(in) ::  pkelhno3(nbins) !< Kelvin effect for HNO3
    58315822    REAL(wp), INTENT(in) ::  pkelnh3(nbins)  !< Kelvin effect for NH3
    5832     REAL(wp), INTENT(in) ::  pmols(nbins,7)
    58335823!-- Saturation ratios
    58345824    REAL(wp), INTENT(out) ::  psathno3(nbins) !<
     
    70357025 SUBROUTINE salsa_diagnostics( i, j )
    70367026 
    7037     USE arrays_3d,                                                             &
    7038         ONLY:  p, pt, zu
    7039        
    7040     USE basic_constants_and_equations_mod,                                     &
    7041         ONLY: g
    7042    
    7043     USE control_parameters,                                                    &
    7044         ONLY:  pt_surface, surface_pressure
    7045        
    70467027    USE cpulog,                                                                &
    70477028        ONLY:  cpu_log, log_point_s
     
    72287209        ONLY:  advec_s_up
    72297210    USE arrays_3d,                                                             &
    7230         ONLY:  ddzu, hyp, pt, rdf_sc, tend
     7211        ONLY:  ddzu, rdf_sc, tend
    72317212    USE diffusion_s_mod,                                                       &
    72327213        ONLY:  diffusion_s
     
    72347215        ONLY:  wall_flags_0
    72357216    USE pegrid,                                                                &
    7236         ONLY:  threads_per_task, myid     
     7217        ONLY:  threads_per_task
    72377218    USE surface_mod,                                                           &
    72387219        ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
     
    79127893    INTEGER(iwp) ::  j           !< loop index: y-direction
    79137894    INTEGER(iwp) ::  k           !< loop index: z-direction
    7914     INTEGER(iwp) ::  kg          !< loop index: z-direction (gases)
    79157895    INTEGER(iwp) ::  n_dt        !< number of time steps in the emission file
    79167896    INTEGER(iwp) ::  nc_stat     !< local variable for storing the result of
     
    79197899    INTEGER(iwp) ::  ncat        !< Number of emission categories
    79207900    INTEGER(iwp) ::  ng_file     !< Number of grid-points in file (gases) 
    7921     INTEGER(iwp) ::  num_vars    !< number of variables in input file
    79227901    INTEGER(iwp) ::  nz_file     !< number of grid-points in file     
    79237902    INTEGER(iwp) ::  n           !< loop index
     
    79387917!-- 1 = traffic, 2 = road dust, 3 = wood combustion, 4 = other
    79397918!-- Mass fractions: H2SO4, OC, BC, DU, SS, HNO3, NH3
    7940     CHARACTER(LEN=15), DIMENSION(ndc) ::  cat_name_table = &!< emission category
    7941                                          (/'road traffic   ','road dust      ',&
    7942                                            'wood combustion','other          '/)
     7919!    CHARACTER(LEN=15), DIMENSION(ndc) ::  cat_name_table = &!< emission category
     7920!                                         (/'road traffic   ','road dust      ',&
     7921!                                           'wood combustion','other          '/)
    79437922    REAL(wp), DIMENSION(ndc) ::  avg_density        !< average density
    79447923    REAL(wp), DIMENSION(ndc) ::  conversion_factor  !< unit conversion factor 
     
    84458424 
    84468425    USE arrays_3d,                                                             &
    8447         ONLY: hyp, pt, rho_air_zw
     8426        ONLY: rho_air_zw
    84488427 
    84498428    USE surface_mod,                                                           &
     
    84558434    TYPE(surf_type), INTENT(inout) :: surface  !< respective surface type
    84568435    INTEGER(iwp) ::  b  !< loop index
    8457     INTEGER(iwp) ::  ee  !< loop index
    8458     INTEGER(iwp) ::  g   !< loop index
    84598436    INTEGER(iwp) ::  i   !< loop index
    84608437    INTEGER(iwp) ::  j   !< loop index
     
    84638440    INTEGER(iwp) ::  n   !< loop index for emission categories
    84648441    INTEGER(iwp) ::  c   !< loop index
    8465     INTEGER(iwp) ::  ss  !< loop index
    84668442   
    84678443    DO  m = 1, surface%ns
     
    86198595    TYPE(surf_type), INTENT(inout) ::  surface  !< respective surface type
    86208596     
    8621     INTEGER(iwp) ::  ee !< index: end
    86228597    INTEGER(iwp) ::  i  !< loop index
    86238598    INTEGER(iwp) ::  j  !< loop index
    86248599    INTEGER(iwp) ::  k  !< loop index
    86258600    INTEGER(iwp) ::  c  !< loop index
    8626     INTEGER(iwp) ::  ss !<index: start
    86278601   
    86288602!
     
    92429216    REAL(wp), DIMENSION(:,:,:), POINTER ::  to_be_resorted           !< pointer
    92439217   
     9218!
     9219!-- Next statement is to avoid compiler warning about unused variable. May be removed in future.
     9220    IF ( two_d )  CONTINUE
    92449221   
    92459222    found = .TRUE.
  • palm/trunk/SOURCE/surface_layer_fluxes_mod.f90

    r3745 r3787  
    2626! -----------------
    2727! $Id$
     28! unused variables removed
     29!
     30! 3745 2019-02-15 18:57:56Z suehring
    2831! Bugfix, missing calculation of 10cm temperature at vertical building walls,
    2932! required for indoor model
     
    297300    INTEGER(iwp) ::  k              !< loop index z direction
    298301    INTEGER(iwp) ::  l              !< loop index for surf type
    299     INTEGER(iwp) ::  li_bnd  = 7500 !< Lookup table index of the last time step
    300302
    301303    INTEGER(iwp), PARAMETER ::  num_steps = 15000  !< number of steps in the lookup table
     
    308310    LOGICAL      ::  surf_vertical     !< Flag indicating vertical surfaces
    309311
    310     REAL(wp), DIMENSION(0:num_steps-1) :: rib_tab,  & !< Lookup table bulk Richardson number
    311                                           ol_tab      !< Lookup table values of L
    312 
    313312    REAL(wp)     ::  e_s,               & !< Saturation water vapor pressure
    314313                     ol_max = 1.0E6_wp, & !< Maximum Obukhov length
    315                      rib_max,           & !< Maximum Richardson number in lookup table
    316                      rib_min,           & !< Minimum Richardson number in lookup table
    317314                     z_mo                 !< Height of the constant flux layer where MOST is assumed
    318315
     
    726723       IMPLICIT NONE
    727724
    728        INTEGER(iwp) :: li,         & !< Index for loop to create lookup table
    729                        num_steps_n   !< Number of non-stretched zeta steps
    730 
    731        LOGICAL :: terminate_run_l = .FALSE.    !< Flag to terminate run (global)
    732 
    733        REAL(wp), PARAMETER ::  zeta_stretch = -10.0_wp !< Start of stretching in the free convection limit
    734                                
    735        REAL(wp), DIMENSION(:), ALLOCATABLE :: zeta_tmp
    736 
    737 
    738        REAL(wp) :: zeta_step,            & !< Increment of zeta
    739                    regr      = 1.01_wp,  & !< Stretching factor of zeta_step in the free convection limit
    740                    regr_old  = 1.0E9_wp, & !< Stretching factor of last iteration step
    741                    z0h_min   = 0.0_wp,   & !< Minimum value of z0h to create table
    742                    z0_min    = 0.0_wp      !< Minimum value of z0 to create table
    743 
    744725
    745726       CALL location_message( 'initializing surface layer', .FALSE. )
    746 
    747727
    748728!
     
    1015995
    1016996       INTEGER(iwp) ::  iter    !< Newton iteration step
    1017        INTEGER(iwp) ::  li      !< look index
    1018997       INTEGER(iwp) ::  m       !< loop variable over all horizontal wall elements
    1019998
     
    20161995       IMPLICIT NONE
    20171996
    2018        CHARACTER (LEN = *), INTENT(IN)       :: z_char          !< string identifier to identify z level
    2019        INTEGER(iwp)                          :: i, j, k, l, m   !< running indices
     1997       CHARACTER (LEN = *), INTENT(IN)       :: z_char       !< string identifier to identify z level
     1998       INTEGER(iwp)                          :: i, j, k, m   !< running indices
    20201999
    20212000       
Note: See TracChangeset for help on using the changeset viewer.