Ignore:
Timestamp:
Apr 8, 2019 6:41:49 PM (5 years ago)
Author:
knoop
Message:

Moved "photolysis_scheme", "chem_species" and "phot_frequen" to chem_modules

File:
1 edited

Legend:

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

    r3835 r3876  
    9494    CHARACTER (LEN=80) ::  mode_emis      = 'PARAMETERIZED'     !< namelist parameter: mode of chemistry emissions - DEFAULT, EXPERT, PARAMETERIZED
    9595    CHARACTER (LEN=80) ::  time_fac_type  = 'MDH'               !< namelist parameter: type of time treatment in the mode_emis DEFAULT - HOUR, MDH
    96    
     96    CHARACTER (LEN=10) ::  photolysis_scheme                    !< 'constant',
     97                                                                !< 'simple' (Simple parameterisation from MCM, Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
     98                                                                !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282) STILL NOT IMPLEMENTED
     99
    97100    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'  !< namelist parameter: names of species with given fluxes (see csflux)
    98101    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'  !< namelist parameter: tbc...???
     
    183186    REAL, PARAMETER ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
    184187    REAL, PARAMETER ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
     188!
     189!-  Define chemical variables within chem_species
     190    TYPE species_def
     191       CHARACTER(LEN=15)                            ::  name         !< name of chemical species
     192       CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3 for aerosol tracers)
     193       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace gases
     194       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_av      !< averaged concentrations
     195       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time level
     196       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc for previous sub-timestep (Runge-Kutta)
     197       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace gases at surface
     198       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at south face of grid box of chemical species (='cs')
     199       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation flux at south face of grid box of chemical species
     200       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at left face of grid box of chemical species (='cs')
     201       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation flux at left face of grid box of chemical species
     202       REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical species
     203    END TYPE species_def
     204!
     205!-- Define photolysis frequencies in phot_frequen
     206    TYPE photols_def
     207       CHARACTER(LEN=15)                            :: name          !< name of pgotolysis frequency
     208       CHARACTER(LEN=15)                            :: unit          !< unit (1/s)
     209       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     :: freq          !< photolysis frequency
     210    END TYPE photols_def
     211
     212
     213    TYPE(species_def), ALLOCATABLE, DIMENSION(:), TARGET ::  chem_species
     214    TYPE(photols_def), ALLOCATABLE, DIMENSION(:), TARGET ::  phot_frequen
    185215
    186216    SAVE
Note: See TracChangeset for help on using the changeset viewer.