Ignore:
Timestamp:
Dec 7, 2018 2:14:11 PM (5 years ago)
Author:
banzhafs
Message:

chem_emissions_mod and chem_modules update to comply PALM coding rules

File:
1 edited

Legend:

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

    r3458 r3611  
    2727! -----------------
    2828! $Id$
     29! Minor formatting
     30!
     31! 3458 2018-10-30 14:51:23Z kanani
    2932! from chemistry branch r3443:
    3033! ??
    31 ! 
     34!
    3235! 3298 2018-10-02 12:21:11Z kanani
    3336! - Minor formatting
     
    7780    PUBLIC spc_names
    7881
    79     INTEGER(iwp), DIMENSION(99)  :: cs_pr_index            = 0
    80     INTEGER(iwp)  :: ibc_cs_b                                                      !< integer flag for bc_cs_b
    81     INTEGER(iwp)  :: ibc_cs_t                                                      !< integer flag for bc_cs_t
    82     INTEGER(iwp)  :: cs_pr_count                           = 0
    83     INTEGER(iwp)  :: max_pr_cs                             = 0
    84     INTEGER(iwp)  :: cs_vertical_gradient_level_ind(99,10) = -9999                 !< grid index values of cs_vertical_gradient_level_ind(s)
    85 
    86     LOGICAL       :: constant_top_csflux(99)               = .TRUE.                !< chem spcs at the top  orig .TRUE.
    87     LOGICAL       :: constant_csflux(99)                   = .TRUE.                !< chem spcs at namelist parameter   orig TRUE
    88     LOGICAL       :: call_chem_at_all_substeps             = .FALSE.               !< namelist parameter
    89     LOGICAL       :: chem_debug0                           = .FALSE.               !< namelist parameter flag for minimum print output
    90     LOGICAL       :: chem_debug1                           = .FALSE.               !< namelist parameter flag for print output
    91     LOGICAL       :: chem_debug2                           = .FALSE.               !< namelist parameter flag for further print output
    92     LOGICAL       :: chem_gasphase_on                      = .TRUE.                !< namelist parameter
    93     LOGICAL       :: emission_output_required              = .TRUE.                !< Logical Variable for requiring Emission Outputs
    94     LOGICAL       :: do_emis                               = .FALSE.               !< Flag for turning on chemistry emissions
    95     LOGICAL       :: cs_pr_namelist_found                  = .FALSE.               !< Namelist parameter: Names of t
    96     LOGICAL       :: do_depo                               = .FALSE.               !< namelist parameter for activation of deposition calculation
    97 
    98 
    99 
     82    INTEGER(iwp), DIMENSION(99) :: cs_pr_index            = 0
     83    INTEGER(iwp) :: ibc_cs_b                                                      !< integer flag for bc_cs_b
     84    INTEGER(iwp) :: ibc_cs_t                                                      !< integer flag for bc_cs_t
     85    INTEGER(iwp) :: cs_pr_count                           = 0
     86    INTEGER(iwp) :: max_pr_cs                             = 0
     87    INTEGER(iwp) :: cs_vertical_gradient_level_ind(99,10) = -9999                 !< grid index values of cs_vertical_gradient_level_ind(s)
     88
     89    LOGICAL      :: constant_top_csflux(99)               = .TRUE.                !< chem spcs at the top  orig .TRUE.
     90    LOGICAL      :: constant_csflux(99)                   = .TRUE.                !< chem spcs at namelist parameter   orig TRUE
     91    LOGICAL      :: call_chem_at_all_substeps             = .FALSE.               !< namelist parameter
     92    LOGICAL      :: chem_debug0                           = .FALSE.               !< namelist parameter flag for minimum print output
     93    LOGICAL      :: chem_debug1                           = .FALSE.               !< namelist parameter flag for print output
     94    LOGICAL      :: chem_debug2                           = .FALSE.               !< namelist parameter flag for further print output
     95    LOGICAL      :: chem_gasphase_on                      = .TRUE.                !< namelist parameter
     96    LOGICAL      :: emission_output_required              = .TRUE.                !< Logical Variable for requiring Emission Outputs
     97    LOGICAL      :: do_emis                               = .FALSE.               !< Flag for turning on chemistry emissions
     98    LOGICAL      :: cs_pr_namelist_found                  = .FALSE.               !< Namelist parameter: Names of t
     99    LOGICAL      :: do_depo                               = .FALSE.               !< namelist parameter for activation of deposition calculation
     100
     101
     102!
    100103!-- Namelist parameters for creating initial chemistry profiles
    101     REAL(wp) :: wall_csflux (99,0:5)               = 0.0_wp                        !< namelist parameter
    102     REAL(wp) :: cs_vertical_gradient (99,10)       = 0.0_wp                        !< namelist parameter
    103     REAL(wp) :: cs_vertical_gradient_level (99,10) = -999999.9_wp                  !< namelist parameter
    104     REAL(wp) :: top_csflux ( 99 )                  = 0.0_wp                        !< namelist parameter
    105     REAL(wp) :: cs_surface_initial_change(99)      = 0.0_wp                        !< namelist parameter
    106     REAL(wp) :: surface_csflux(99 )                = 0.0_wp                        !< namelist parameter: fluxes where 'surface_csflux_name' is in the namelist
    107 
    108     REAL(wp), DIMENSION(:),  ALLOCATABLE              :: bc_cs_t_val
    109     REAL(wp), DIMENSION(:),  ALLOCATABLE              ::  css                      !< scaling parameter for chem spcs
    110     REAL(wp), DIMENSION(99)                           :: cs_surface = 0.0_wp       !< Namelist parameter: Surface conc of chem spcs'
    111     REAL(wp), DIMENSION(99,100)                       :: cs_heights = 9999999.9_wp !< Namelist parameter: Height lvls(m) for cs_profiles
    112     REAL(wp), DIMENSION(99,100)                       :: cs_profile = 9999999.9_wp !< Namelist parameter: Chem conc for each spcs defined
     104    REAL(wp) ::  wall_csflux (99,0:5)               = 0.0_wp                        !< namelist parameter
     105    REAL(wp) ::  cs_vertical_gradient (99,10)       = 0.0_wp                        !< namelist parameter
     106    REAL(wp) ::  cs_vertical_gradient_level (99,10) = -999999.9_wp                  !< namelist parameter
     107    REAL(wp) ::  top_csflux ( 99 )                  = 0.0_wp                        !< namelist parameter
     108    REAL(wp) ::  cs_surface_initial_change(99)      = 0.0_wp                        !< namelist parameter
     109    REAL(wp) ::  surface_csflux(99 )                = 0.0_wp                        !< namelist parameter: fluxes where 'surface_csflux_name' is in the namelist
     110
     111    REAL(wp), DIMENSION(:), ALLOCATABLE               :: bc_cs_t_val
     112    REAL(wp), DIMENSION(:), ALLOCATABLE               ::  css                       !< scaling parameter for chem spcs
     113    REAL(wp), DIMENSION(99)                           ::  cs_surface = 0.0_wp       !< Namelist parameter: Surface conc of chem spcs'
     114    REAL(wp), DIMENSION(99,100)                       ::  cs_heights = 9999999.9_wp !< Namelist parameter: Height lvls(m) for cs_profiles
     115    REAL(wp), DIMENSION(99,100)                       ::  cs_profile = 9999999.9_wp !< Namelist parameter: Chem conc for each spcs defined
    113116
    114117
    115118#if defined( __nopointer )
    116     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs                        !< chem spcs
    117     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs_p                      !< prognostic value of chem spc
    118     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: tcs_m                     !< weighted tendency of cs for previous sub-timestep (Runge-Kutta)
     119    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  cs                        !< chem spcs
     120    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  cs_p                      !< prognostic value of chem spc
     121    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   ::  tcs_m                     !< weighted tendency of cs for previous sub-timestep (Runge-Kutta)
    119122
    120123#else                                                               
    121 ! use pointers cs, cs_p and tcs_m to point arrays cs_1, cs_2, and cs_3
    122     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_1                      !< pointer for swapping of timelevels for respective quantity
    123     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_2                      !< pointer for swapping of timelevels for respective quantity
    124     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_3                      !< pointer for swapping of timelevels for respective quantity
    125     REAL(wp), DIMENSION(:,:,:), POINTER               :: cs                        !< pointer: sgs chem spcs)
    126     REAL(wp), DIMENSION(:,:,:), POINTER               :: cs_p                      !< pointer: prognostic value of sgs chem spcs
    127     REAL(wp), DIMENSION(:,:,:), POINTER               :: tcs_m                     !< pointer:
     124!
     125!-- Use pointers cs, cs_p and tcs_m to point arrays cs_1, cs_2, and cs_3
     126    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1                      !< pointer for swapping of timelevels for respective quantity
     127    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2                      !< pointer for swapping of timelevels for respective quantity
     128    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3                      !< pointer for swapping of timelevels for respective quantity
     129    REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs                        !< pointer: sgs chem spcs)
     130    REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs_p                      !< pointer: prognostic value of sgs chem spcs
     131    REAL(wp), DIMENSION(:,:,:), POINTER               ::  tcs_m                     !< pointer:
    128132
    129133#endif                                                                           
    130134 
    131     CHARACTER (LEN=20)                 :: bc_cs_b             = 'dirichlet'        !< namelist parameter
    132     CHARACTER (LEN=20)                 :: bc_cs_t             = 'initial_gradient' !< namelist parameter
    133     CHARACTER (LEN=11), DIMENSION(99)  :: cs_name             = 'novalue'          !< Namelist parameter: chem spcs names
    134     CHARACTER (LEN=11), DIMENSION(99)  :: cs_profile_name     = 'novalue'          !< Namelist parameter: Names of the chem for profiles
    135     CHARACTER (LEN=11), DIMENSION(99)  :: surface_csflux_name = 'novalue'          !< Namelist parameter: chem species surface fluxes names
    136                                                                                    !< active chem spcs, default is 'novalue')  ????
    137     CHARACTER (LEN=80)                 :: mode_emis           ='PARAMETERIZED'     !< Mode of chemistry emissions: DEFAULT .OR. EXPERT .OR.
    138                                                                                    ! PARAMETERIZED
    139     CHARACTER (LEN=80)                 :: time_fac_type       ='MDH'               !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
    140     CHARACTER (LEN=80)                 :: daytype_mdh         ='workday'           !< Type of day in the MDH case: workday, weekend, holiday
    141     CHARACTER (LEN=11), DIMENSION(99)  :: data_output_pr_cs   = 'novalue'          !< Namelist parameter: Names of the che    m for profile output
    142                                                                                    !< by cs_name for each height lvls defined by cs_heights
     135    CHARACTER (LEN=20)                ::  bc_cs_b             = 'dirichlet'         !< namelist parameter
     136    CHARACTER (LEN=20)                ::  bc_cs_t             = 'initial_gradient' !< namelist parameter
     137    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'           !< Namelist parameter: chem spcs names
     138    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'           !< Namelist parameter: Names of the chem for profiles
     139    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'           !< Namelist parameter: chem species surface fluxes names
     140                                                                                    !< active chem spcs, default is 'novalue')  ????
     141    CHARACTER (LEN=80)                ::  mode_emis           ='PARAMETERIZED'      !< Mode of chemistry emissions: DEFAULT .OR. EXPERT .OR.
     142                                                                                    !< PARAMETERIZED
     143    CHARACTER (LEN=80)                ::  time_fac_type       ='MDH'                !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
     144    CHARACTER (LEN=80)                ::  daytype_mdh         ='workday'            !< Type of day in the MDH case: workday, weekend, holiday
     145    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'           !< Namelist parameter: Names of the che    m for profile output
     146                                                                                    !< by cs_name for each height lvls defined by cs_heights
    143147!
    144148!-- Namelist parameters for chem_emissions
     
    150154    REAL(wp) ::  emiss_factor_main ( 99 ) = -9999.0_wp
    151155    REAL(wp) ::  emiss_factor_side ( 99 ) = -9999.0_wp
    152    
     156!   
    153157!-- Other Emissions Variables
    154158    INTEGER(iwp) ::  nspec_out                                                     !< Output of routine chem_emis_matching with
    155159                                                                                   !< number of matched species
    156     REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)         :: emis_distribution          !> Emissions Final Values (main module output)
    157 
    158     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_input           !< Index of Input chem species for matching routine
    159     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_model           !< Index of Model chem species for matching routine
    160     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_voc_input       !< index of VOC input components matching the model's VOCs
    161     INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_voc_model       !< index of VOC model species matching the input VOCs comp.
    162     INTEGER(iwp),DIMENSION(:)                        :: match_spec_pm(1:3)         !< results of matching the input and model's PMs
    163     INTEGER(iwp),DIMENSION(:)                        :: match_spec_nox(1:2)        !< results of matching the input and model's NOx
    164     INTEGER(iwp),DIMENSION(:)                        :: match_spec_sox(1:2)        !< results of matching the input and model's SOx!
    165                                                                                    ! TBD: evaluate whether to make them allocatable
    166                                                                                    ! and allocate their dimension in the matching
    167                                                                                    ! routine according to the number of components
    168                                                                                    ! matching between the model and the input files
    169 
     160    REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:) ::  emis_distribution                 !> Emissions Final Values (main module output)
     161
     162    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)    ::  match_spec_input                  !< Index of Input chem species for matching routine
     163    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)    ::  match_spec_model                  !< Index of Model chem species for matching routine
     164    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)    ::  match_spec_voc_input              !< index of VOC input components matching the model's VOCs
     165    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)    ::  match_spec_voc_model              !< index of VOC model species matching the input VOCs comp.
     166    INTEGER(iwp),DIMENSION(:)                ::  match_spec_pm(1:3)                !< results of matching the input and model's PMs
     167    INTEGER(iwp),DIMENSION(:)                ::  match_spec_nox(1:2)               !< results of matching the input and model's NOx
     168    INTEGER(iwp),DIMENSION(:)                ::  match_spec_sox(1:2)               !< results of matching the input and model's SOx!
     169                                                                                 
     170
     171!
     172!-- Selected atomic/molecular weights:
     173    REAL, PARAMETER        ::  xm_H     =    1.00790e-3           !< kg/mol
     174    REAL, PARAMETER        ::  xm_N     =   14.00670e-3           !< kg/mol
     175    REAL, PARAMETER        ::  xm_C     =   12.01115e-3           !< kg/mol
     176    REAL, PARAMETER        ::  xm_S     =   32.06400e-3           !< kg/mol
     177    REAL, PARAMETER        ::  xm_O     =   15.99940e-3           !< kg/mol
     178    REAL, PARAMETER        ::  xm_F     =   18.99840e-3           !< kg/mol
     179    REAL, PARAMETER        ::  xm_Na    =   22.98977e-3           !< kg/mol
     180    REAL, PARAMETER        ::  xm_Cl    =   35.45300e-3           !< kg/mol
     181    REAL, PARAMETER        ::  xm_Rn222 =  222.00000e-3           !< kg/mol
     182    REAL, PARAMETER        ::  xm_Pb210 =  210.00000e-3           !< kg/mol
     183    REAL, PARAMETER        ::  xm_Ca    =   40.07800e-3           !< kg/mol
     184    REAL, PARAMETER        ::  xm_K     =   39.09800e-3           !< kg/mol
     185    REAL, PARAMETER        ::  xm_Mg    =   24.30500e-3           !< kg/mol
     186    REAL, PARAMETER        ::  xm_Pb    =  207.20000e-3           !< kg/mol
     187    REAL, PARAMETER        ::  xm_Cd    =  112.41000e-3           !< kg/mol
    170188   
    171     !-- Selected atomic/molecular weights:
     189    REAL, PARAMETER        ::  xm_h2o   = xm_H * 2 + xm_O         !< kg/mol
     190    REAL, PARAMETER        ::  xm_o3    = xm_O * 3                !< kg/mol
     191    REAL, PARAMETER        ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< kg/mol
     192    REAL, PARAMETER        ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< kg/mol
     193    REAL, PARAMETER        ::  xm_NH4   = xm_N + xm_H * 4         !< kg/mol
     194    REAL, PARAMETER        ::  xm_SO4   = xm_S + xm_O * 4         !< kg/mol
     195    REAL, PARAMETER        ::  xm_NO3   = xm_N + xm_O * 3         !< kg/mol
     196    REAL, PARAMETER        ::  xm_CO2   = xm_C + xm_O * 2         !< kg/mol
    172197   
    173     REAL, PARAMETER        ::  xm_H     =    1.00790e-3           ! kg/mol
    174     REAL, PARAMETER        ::  xm_N     =   14.00670e-3           ! kg/mol
    175     REAL, PARAMETER        ::  xm_C     =   12.01115e-3           ! kg/mol
    176     REAL, PARAMETER        ::  xm_S     =   32.06400e-3           ! kg/mol
    177     REAL, PARAMETER        ::  xm_O     =   15.99940e-3           ! kg/mol
    178     REAL, PARAMETER        ::  xm_F     =   18.99840e-3           ! kg/mol
    179     REAL, PARAMETER        ::  xm_Na    =   22.98977e-3           ! kg/mol
    180     REAL, PARAMETER        ::  xm_Cl    =   35.45300e-3           ! kg/mol
    181     REAL, PARAMETER        ::  xm_Rn222 =  222.00000e-3           ! kg/mol
    182     REAL, PARAMETER        ::  xm_Pb210 =  210.00000e-3           ! kg/mol
    183     REAL, PARAMETER        ::  xm_Ca    =   40.07800e-3           ! kg/mol
    184     REAL, PARAMETER        ::  xm_K     =   39.09800e-3           ! kg/mol
    185     REAL, PARAMETER        ::  xm_Mg    =   24.30500e-3           ! kg/mol
    186     REAL, PARAMETER        ::  xm_Pb    =  207.20000e-3           ! kg/mol
    187     REAL, PARAMETER        ::  xm_Cd    =  112.41000e-3           ! kg/mol
    188    
    189     REAL, PARAMETER        ::  xm_h2o   = xm_H * 2 + xm_O         ! kg/mol
    190     REAL, PARAMETER        ::  xm_o3    = xm_O * 3                ! kg/mol
    191     REAL, PARAMETER        ::  xm_N2O5  = xm_N * 2 + xm_O * 5     ! kg/mol
    192     REAL, PARAMETER        ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  ! kg/mol
    193     REAL, PARAMETER        ::  xm_NH4   = xm_N + xm_H * 4         ! kg/mol
    194     REAL, PARAMETER        ::  xm_SO4   = xm_S + xm_O * 4         ! kg/mol
    195     REAL, PARAMETER        ::  xm_NO3   = xm_N + xm_O * 3         ! kg/mol
    196     REAL, PARAMETER        ::  xm_CO2   = xm_C + xm_O * 2         ! kg/mol
    197    
    198     ! mass of air
    199     REAL, PARAMETER        ::  xm_air   =  28.964e-3              ! kg/mol
     198!
     199!-- mass of air
     200    REAL, PARAMETER        ::  xm_air   =  28.964e-3              !< kg/mol
    200201       
    201     ! dummy weight, used for complex molecules:
     202!
     203!-- dummy weight, used for complex molecules:
    202204    REAL, PARAMETER        ::  xm_dummy =  1000.0e-3              ! kg/mol
    203205
Note: See TracChangeset for help on using the changeset viewer.