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

    r3862 r3876  
    318318
    319319    LOGICAL ::  nest_chemistry = .TRUE.  !< flag for nesting mode of chemical species, independent on parent or not
    320 !
    321 !-  Define chemical variables within chem_species
    322     TYPE species_def
    323        CHARACTER(LEN=15)                            ::  name         !< name of chemical species
    324        CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3 for aerosol tracers)
    325        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace gases
    326        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_av      !< averaged concentrations
    327        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time level
    328        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc for previous sub-timestep (Runge-Kutta)
    329        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace gases at surface
    330        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at south face of grid box of chemical species (='cs')
    331        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation flux at south face of grid box of chemical species
    332        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at left face of grid box of chemical species (='cs')
    333        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation flux at left face of grid box of chemical species
    334        REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical species
    335     END TYPE species_def
    336 !
    337 !-- Define photolysis frequencies in phot_frequen
    338     TYPE photols_def                                                           
    339        CHARACTER(LEN=15)                            :: name          !< name of pgotolysis frequency
    340        CHARACTER(LEN=15)                            :: unit          !< unit (1/s)
    341        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     :: freq          !< photolysis frequency
    342     END TYPE photols_def
    343 
    344 
    345     TYPE(species_def), ALLOCATABLE, DIMENSION(:), TARGET, PUBLIC ::  chem_species
    346     TYPE(photols_def), ALLOCATABLE, DIMENSION(:), TARGET, PUBLIC ::  phot_frequen 
    347320
    348321    REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:,:), TARGET ::  spec_conc_1  !< pointer for swapping of timelevels for conc
     
    374347
    375348    REAL(kind=wp), PUBLIC ::  cs_time_step = 0._wp
    376     CHARACTER(10), PUBLIC ::  photolysis_scheme
    377                               !< 'constant',
    378                               !< 'simple' (Simple parameterisation from MCM, Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
    379                               !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282) STILL NOT IMPLEMENTED
    380 
    381349
    382350!
     
    445413    PUBLIC nspec               !< number of gas phase chemical species including constant compound (e.g. N2)
    446414    PUBLIC nvar                !< number of variable gas phase chemical species (nvar <= nspec)
    447     PUBLIC photols_def         !< type defining phot_frequen
    448     PUBLIC species_def         !< type defining chem_species
    449415    PUBLIC spc_names           !< names of gas phase chemical species (come from KPP) (come from KPP)
    450416    PUBLIC spec_conc_2 
Note: See TracChangeset for help on using the changeset viewer.