Changeset 3827 for palm


Ignore:
Timestamp:
Mar 27, 2019 5:20:32 PM (5 years ago)
Author:
forkel
Message:

some formatting and reordering of lines

File:
1 edited

Legend:

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

    r3820 r3827  
    2727! -----------------
    2828! $Id$
     29! some formatting  and reordering (ecc)
     30!
     31! 3820 2019-03-27 11:53:41Z forkel
    2932! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
    3033!
     
    9093    CHARACTER (LEN=20)                ::  bc_cs_t             = 'initial_gradient'  !< namelist parameter
    9194    CHARACTER (LEN=30)                ::  chem_mechanism      = 'phstatp'           !< KPP chmical mechanism
    92     CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'           !< Namelist parameter: chem spcs names
    93     CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'           !< Namelist parameter: Names of the chem for profiles
    94     CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'           !< Namelist parameter: Names of the chem species for profile output
    9595                                                                                    !< by cs_name for each height lvls defined by cs_heights
    9696    CHARACTER (LEN=80)                ::  daytype_mdh         ='workday'            !< Type of day in the MDH case: workday, weekend, holiday
    9797    CHARACTER (LEN=80)                ::  mode_emis           ='PARAMETERIZED'      !< Mode of chemistry emissions: DEFAULT .OR. EXPERT .OR.
    9898                                                                                    !< PARAMETERIZED
     99    CHARACTER (LEN=80)                ::  time_fac_type       ='MDH'                !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
     100    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'           !< Namelist parameter: chem spcs names
     101    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'           !< Namelist parameter: Names of the chem for profiles
     102    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'           !< Namelist parameter: Names of the chem species for profile output
    99103    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'           !< Namelist parameter: chem species names with surface fluxes specified
    100104                                                                                    !< active chem spcs, default is 'novalue')  ????
    101     CHARACTER (LEN=80)                ::  time_fac_type       ='MDH'                !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
    102105
    103     INTEGER(iwp), DIMENSION(99)            ::  cs_pr_index                           = 0      !< index for chemical species profile (ecc)
    104     INTEGER(iwp)                           ::  cs_pr_count                           = 0      !< namelist parameter : No. of species profiles (ecc)
    105     INTEGER(iwp)                           ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of cs_vertical_gradient_level_ind(s)
    106     INTEGER(iwp)                           ::  ibc_cs_b                                       !< integer flag for bc_cs_b
    107     INTEGER(iwp)                           ::  ibc_cs_t                                       !< integer flag for bc_cs_t
    108     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_input                               !< Index of Input chem species for matching routine
    109     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_model                               !< Index of Model chem species for matching routine
    110     INTEGER(iwp),DIMENSION(:)              ::  match_spec_nox(1:2)                            !< results of matching the input and model's NOx
    111     INTEGER(iwp),DIMENSION(:)              ::  match_spec_pm(1:3)                             !< results of matching the input and model's PMs
    112     INTEGER(iwp),DIMENSION(:)              ::  match_spec_sox(1:2)                            !< results of matching the input and model's SOx!
    113     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_voc_input                           !< index of VOC input components matching the model's VOCs
    114     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_voc_model                           !< index of VOC model species matching the input VOCs comp.
    115     INTEGER(iwp)                           ::  main_street_id                        = 0      !< namelist parameter for chem_emissions : ID for main streets
    116     INTEGER(iwp)                           ::  max_pr_cs                             = 0      !< namelist parameter : Max no. of species profiles (ecc)
    117     INTEGER(iwp)                           ::  max_street_id                         = 0      !< namelist parameter for chem_emissions : maximum street IDs     
    118     INTEGER(iwp)                           ::  nspec_out                                      !< Output of routine chem_emis_matching with
    119     INTEGER(iwp)                           ::  side_street_id                        = 0      !< namelist paramtger for chem_emissions : ID for side streets
     106    INTEGER(iwp)                          ::  cs_pr_count                           = 0      !< namelist parameter : No. of species profiles (ecc)
     107    INTEGER(iwp)                          ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of cs_vertical_gradient_level_ind(s)
     108    INTEGER(iwp)                          ::  ibc_cs_b                                       !< integer flag for bc_cs_b
     109    INTEGER(iwp)                          ::  ibc_cs_t                                       !< integer flag for bc_cs_t
     110    INTEGER(iwp)                          ::  main_street_id                        = 0      !< namelist parameter for chem_emissions : ID for main streets 
     111    INTEGER(iwp)                          ::  max_pr_cs                             = 0      !< namelist parameter : Max no. of species profiles (ecc)
     112    INTEGER(iwp)                          ::  max_street_id                         = 0      !< namelist parameter for chem_emissions : maximum street IDs     
     113    INTEGER(iwp)                          ::  nspec_out                                      !< Output of routine chem_emis_matching with
     114    INTEGER(iwp)                          ::  side_street_id                        = 0      !< namelist paramtger for chem_emissions : ID for side streets
     115    INTEGER(iwp),DIMENSION(99)            ::  cs_pr_index                           = 0      !< index for chemical species profile (ecc)
     116    INTEGER(iwp),DIMENSION(:)             ::  match_spec_nox(1:2)                            !< results of matching the input and model's NOx
     117    INTEGER(iwp),DIMENSION(:)             ::  match_spec_pm(1:3)                             !< results of matching the input and model's PMs
     118    INTEGER(iwp),DIMENSION(:)             ::  match_spec_sox(1:2)                            !< results of matching the input and model's SOx!
     119    INTEGER(iwp),DIMENSION(:),ALLOCATABLE ::  match_spec_input                               !< Index of Input chem species for matching routine
     120    INTEGER(iwp),DIMENSION(:),ALLOCATABLE ::  match_spec_model                               !< Index of Model chem species for matching routine
     121    INTEGER(iwp),DIMENSION(:),ALLOCATABLE ::  match_spec_voc_input                           !< index of VOC input components matching the model's VOCs
     122    INTEGER(iwp),DIMENSION(:),ALLOCATABLE ::  match_spec_voc_model                           !< index of VOC model species matching the input VOCs comp.
    120123
    121124    LOGICAL      ::  constant_top_csflux(99)               = .TRUE.   !< chem spcs at the top  orig .TRUE.
     
    126129    LOGICAL      ::  chem_debug2                           = .FALSE.  !< namelist parameter flag for further print output
    127130    LOGICAL      ::  chem_gasphase_on                      = .TRUE.   !< namelist parameter
    128     LOGICAL      ::  emission_output_required              = .TRUE.   !< Logical Variable for requiring Emission Outputs
    129131    LOGICAL      ::  cs_pr_namelist_found                  = .FALSE.  !< Namelist parameter: Names of t
    130132    LOGICAL      ::  deposition_dry                        = .FALSE.  !< namelist parameter for activation of deposition calculation
    131133    LOGICAL      ::  emissions_anthropogenic               = .FALSE.  !< Flag for turning on anthropogenic emissions
     134    LOGICAL      ::  emission_output_required              = .TRUE.   !< Logical Variable for requiring Emission Outputs
    132135!
    133136!-- Namelist parameters for creating initial chemistry profiles
    134     REAL(wp)                                          ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter : initial surface flux difference
    135     REAL(wp)                                          ::  cs_vertical_gradient(99,10)       = 0.0_wp        !< namelist parameter : vertical gradient
    136     REAL(wp)                                          ::  cs_vertical_gradient_level(99,10) = -999999.9_wp  !< namelist parameter : vertical gradient level
    137     REAL(wp)                                          ::  surface_csflux(99)                = 0.0_wp        !< namelist parameter : fluxes where 'surface_csflux_name' is
    138                                                                                                             !< in the namelist
    139     REAL(wp)                                          ::  top_csflux(99)                    = 0.0_wp        !< namelist parameter : chemical species flux at ceiling
    140     REAL(wp)                                          ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter : chemical species flux lateral
    141     REAL(wp), DIMENSION(:), ALLOCATABLE               ::  bc_cs_t_val                                       !< chemical specices time value at BC
    142     REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs                                                !< pointer: sgs chem spcs)
    143     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1                                              !< pointer for swapping of timelevels for respective quantity
    144     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2                                              !< pointer for swapping of timelevels for respective quantity
    145     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3                                              !< pointer for swapping of timelevels for respective quantity
    146     REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs_p                                              !< pointer: prognostic value of sgs chem spcs
    147     REAL(wp), DIMENSION(:), ALLOCATABLE               ::  css                                               !< scaling parameter for chem spcs
    148     REAL(wp), DIMENSION(99,100)                       ::  cs_profile                        = 9999999.9_wp  !< Namelist parameter: Chem conc for each spcs defined
    149     REAL(wp), DIMENSION(99,100)                       ::  cs_heights                        = 9999999.9_wp  !< Namelist parameter: Height lvls(m) for cs_profiles
    150     REAL(wp), DIMENSION(99)                           ::  cs_surface                        = 0.0_wp        !< Namelist parameter: Surface conc of chem spcs'
    151     REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)          ::  emis_distribution                                 !< Emissions Final Values (main module output)
    152     REAL(wp)                                          ::  emiss_factor_main(99)             = -9999.0_wp    !< emission factor for main streets
    153     REAL(wp)                                          ::  emiss_factor_side(99)             = -9999.0_wp    !< emission factor for side streets
    154     REAL(wp), DIMENSION(:,:,:), POINTER               ::  tcs_m                                             !< pointer: to tcs array (temp)
     137    REAL(wp)                                        ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter : initial surface flux difference
     138    REAL(wp)                                        ::  cs_vertical_gradient(99,10)       = 0.0_wp        !< namelist parameter : vertical gradient
     139    REAL(wp)                                        ::  cs_vertical_gradient_level(99,10) = -999999.9_wp  !< namelist parameter : vertical gradient level
     140    REAL(wp)                                        ::  emiss_factor_main(99)             = -9999.0_wp    !< emission factor for main streets
     141    REAL(wp)                                        ::  emiss_factor_side(99)             = -9999.0_wp    !< emission factor for side streets
     142                                                                                                          !< in the namelist
     143    REAL(wp)                                        ::  surface_csflux(99)                = 0.0_wp        !< namelist parameter : fluxes where 'surface_csflux_name' is
     144    REAL(wp)                                        ::  top_csflux(99)                    = 0.0_wp        !< namelist parameter : chemical species flux at ceiling
     145    REAL(wp)                                        ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter : chemical species flux lateral
     146    REAL(wp),DIMENSION(99)                          ::  cs_surface                        = 0.0_wp        !< Namelist parameter: Surface conc of chem spcs'
     147    REAL(wp),DIMENSION(99,100)                      ::  cs_heights                        = 9999999.9_wp  !< Namelist parameter: Height lvls(m) for cs_profiles
     148    REAL(wp),DIMENSION(99,100)                      ::  cs_profile                        = 9999999.9_wp  !< Namelist parameter: Chem conc for each spcs defined
     149    REAL(wp),DIMENSION(:),ALLOCATABLE               ::  bc_cs_t_val                                       !< chemical specices time value at BC
     150    REAL(wp),DIMENSION(:),ALLOCATABLE               ::  css                                               !< scaling parameter for chem spcs
     151    REAL(wp),DIMENSION(:,:,:,:),ALLOCATABLE         ::  emis_distribution                                 !< Emissions Final Values (main module output)
     152    REAL(wp),DIMENSION(:,:,:,:),ALLOCATABLE, TARGET ::  cs_1                                              !< pointer for swapping of timelevels for respective quantity
     153    REAL(wp),DIMENSION(:,:,:,:),ALLOCATABLE, TARGET ::  cs_2                                              !< pointer for swapping of timelevels for respective quantity
     154    REAL(wp),DIMENSION(:,:,:,:),ALLOCATABLE, TARGET ::  cs_3                                              !< pointer for swapping of timelevels for respective quantity
     155    REAL(wp),DIMENSION(:,:,:),POINTER               ::  cs                                                !< pointer: sgs chem spcs)
     156    REAL(wp),DIMENSION(:,:,:),POINTER               ::  cs_p                                              !< pointer: prognostic value of sgs chem spcs
     157    REAL(wp),DIMENSION(:,:,:),POINTER               ::  tcs_m                                             !< pointer: to tcs array (temp)
    155158!
    156159!-- molecular weights
    157     REAL, PARAMETER        ::  xm_air   =   28.964e-3             !< air      molecular weight (kg/mol)
    158     REAL, PARAMETER        ::  xm_C     =   12.01115e-3           !< C        molecular weight (kg/mol)
    159     REAL, PARAMETER        ::  xm_Ca    =   40.07800e-3           !< Ca       molecular weight (kg/mol)
    160     REAL, PARAMETER        ::  xm_Cd    =  112.41000e-3           !< Cd       molecular weight (kg/mol)
    161     REAL, PARAMETER        ::  xm_Cl    =   35.45300e-3           !< Cl       molecular weight (kg/mol)
    162     REAL, PARAMETER        ::  xm_dummy = 1000.0e-3               !< dummy    molecular weight (kg/mol)
    163     REAL, PARAMETER        ::  xm_F     =   18.99840e-3           !< F        molecular weight (kg/mol)
    164     REAL, PARAMETER        ::  xm_H     =    1.00790e-3           !< H        molecular weight (kg/mol)
    165     REAL, PARAMETER        ::  xm_K     =   39.09800e-3           !< K        molecular weight (kg/mol)
    166     REAL, PARAMETER        ::  xm_Mg    =   24.30500e-3           !< Mg       molecular weight (kg/mol)
    167     REAL, PARAMETER        ::  xm_N     =   14.00670e-3           !< N        molecular weight (kg/mol)
    168     REAL, PARAMETER        ::  xm_Na    =   22.98977e-3           !< Na       molecular weight (kg/mol)
    169     REAL, PARAMETER        ::  xm_O     =   15.99940e-3           !< O        molecular weight (kg/mol)
    170     REAL, PARAMETER        ::  xm_Pb    =  207.20000e-3           !< Pb       molecular weight (kg/mol)
    171     REAL, PARAMETER        ::  xm_Pb210 =  210.00000e-3           !< Pb (210) molecular weight (kg/mol)
    172     REAL, PARAMETER        ::  xm_Rn222 =  222.00000e-3           !< Rn (222) molecular weight (kg/mol)
    173     REAL, PARAMETER        ::  xm_S     =   32.06400e-3           !< S        molecular weight (kg/mol)
    174     REAL, PARAMETER        ::  xm_CO2   = xm_C + xm_O * 2         !< CO2      molecular weight (kg/mol)
    175     REAL, PARAMETER        ::  xm_h2o   = xm_H * 2 + xm_O         !< H2O      molecular weight (kg/mol)
    176     REAL, PARAMETER        ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< HNO3     molecular weight (kg/mol)
    177     REAL, PARAMETER        ::  xm_o3    = xm_O * 3                !< O3       molecular weight (kg/mol)
    178     REAL, PARAMETER        ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< N2O5     molecular weight (kg/mol)
    179     REAL, PARAMETER        ::  xm_NH4   = xm_N + xm_H * 4         !< NH4      molecular weight (kg/mol)
    180     REAL, PARAMETER        ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
    181     REAL, PARAMETER        ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
     160    REAL, PARAMETER ::  xm_air   =   28.964e-3             !< air      molecular weight (kg/mol)
     161    REAL, PARAMETER ::  xm_C     =   12.01115e-3           !< C        molecular weight (kg/mol)
     162    REAL, PARAMETER ::  xm_Ca    =   40.07800e-3           !< Ca       molecular weight (kg/mol)
     163    REAL, PARAMETER ::  xm_Cd    =  112.41000e-3           !< Cd       molecular weight (kg/mol)
     164    REAL, PARAMETER ::  xm_Cl    =   35.45300e-3           !< Cl       molecular weight (kg/mol)
     165    REAL, PARAMETER ::  xm_dummy = 1000.0e-3               !< dummy    molecular weight (kg/mol)
     166    REAL, PARAMETER ::  xm_F     =   18.99840e-3           !< F        molecular weight (kg/mol)
     167    REAL, PARAMETER ::  xm_H     =    1.00790e-3           !< H        molecular weight (kg/mol)
     168    REAL, PARAMETER ::  xm_K     =   39.09800e-3           !< K        molecular weight (kg/mol)
     169    REAL, PARAMETER ::  xm_Mg    =   24.30500e-3           !< Mg       molecular weight (kg/mol)
     170    REAL, PARAMETER ::  xm_N     =   14.00670e-3           !< N        molecular weight (kg/mol)
     171    REAL, PARAMETER ::  xm_Na    =   22.98977e-3           !< Na       molecular weight (kg/mol)
     172    REAL, PARAMETER ::  xm_O     =   15.99940e-3           !< O        molecular weight (kg/mol)
     173    REAL, PARAMETER ::  xm_Pb    =  207.20000e-3           !< Pb       molecular weight (kg/mol)
     174    REAL, PARAMETER ::  xm_Pb210 =  210.00000e-3           !< Pb (210) molecular weight (kg/mol)
     175    REAL, PARAMETER ::  xm_Rn222 =  222.00000e-3           !< Rn (222) molecular weight (kg/mol)
     176    REAL, PARAMETER ::  xm_S     =   32.06400e-3           !< S        molecular weight (kg/mol)
     177    REAL, PARAMETER ::  xm_CO2   = xm_C + xm_O * 2         !< CO2      molecular weight (kg/mol)
     178    REAL, PARAMETER ::  xm_h2o   = xm_H * 2 + xm_O         !< H2O      molecular weight (kg/mol)
     179    REAL, PARAMETER ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< HNO3     molecular weight (kg/mol)
     180    REAL, PARAMETER ::  xm_o3    = xm_O * 3                !< O3       molecular weight (kg/mol)
     181    REAL, PARAMETER ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< N2O5     molecular weight (kg/mol)
     182    REAL, PARAMETER ::  xm_NH4   = xm_N + xm_H * 4         !< NH4      molecular weight (kg/mol)
     183    REAL, PARAMETER ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
     184    REAL, PARAMETER ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
    182185
    183186    SAVE
Note: See TracChangeset for help on using the changeset viewer.