source: palm/trunk/SOURCE/chem_photolysis_mod.f90 @ 4182

Last change on this file since 4182 was 4182, checked in by scharf, 5 years ago
  • corrected "Former revisions" section
  • minor formatting in "Former revisions" section
  • added "Author" section
  • Property svn:keywords set to Id
File size: 9.9 KB
RevLine 
[2425]1!> @file chem_photolysis_mod.f90
2!------------------------------------------------------------------------------!
[2828]3! This file is part of the PALM model system.
[2425]4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
[3298]17! Copyright 2018-2018 Leibniz Universitaet Hannover
18! Copyright 2018-2018 Karlsruhe Institute of Technology
[2425]19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
[3298]24!
[2425]25! Former revisions:
[2828]26! -----------------
[2425]27! $Id: chem_photolysis_mod.f90 4182 2019-08-22 15:20:23Z scharf $
[4182]28! Corrected "Former revisions" section
29!
30! 3876 2019-04-08 18:41:49Z knoop
[3838]31! some formatting and comments added
32!
33! 3824 2019-03-27 15:56:16Z pavelkrc
[3614]34! unused variables removed
35!
[4182]36! 2718 2018-01-02 08:49:38Z maronga
37! Initial revision
38!
39!
40! Authors:
41! --------
42! @author Renate Forkel
43!
[2425]44!------------------------------------------------------------------------------!
45! Description:
46! ------------
47!> photolysis models and interfaces (Adapted from photolysis_model_mod.f90)
[3838]48!> @todo more complex scheme, add shading
[2425]49!------------------------------------------------------------------------------!
50 MODULE chem_photolysis_mod
[2828]51
[3287]52!   USE arrays_3d,                                                             &
53!       ONLY:  dzw, q, ql, zu, zw
[2425]54
55    USE control_parameters,                                                    &
56        ONLY:  time_since_reference_point
57
[3838]58    USE pegrid,                                                                &
59        ONLY: myid, threads_per_task
[2425]60
61    USE indices,                                                               &
[2592]62        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
[2425]63
64    USE control_parameters,                                                    &
65        ONLY:  initializing_actions           
66
[2633]67    USE chem_gasphase_mod,                                                     &
[2425]68        ONLY: nphot, phot_names, phot 
69
[3876]70    USE chem_modules,                                                          &
[2592]71        ONLY: phot_frequen, photolysis_scheme
[2425]72
[2828]73    USE chem_modules,                                                          &
[2633]74        ONLY: chem_debug2
75
[2425]76    USE kinds
77
78#if defined ( __netcdf )
79    USE NETCDF
80#endif
81
82
83    IMPLICIT NONE
84
85
[2592]86!   LOGICAL ::  unscheduled_photolysis_calls = .TRUE., & !< flag parameter indicating whether additional calls of the photolysis code are allowed
87!               constant_albedo = .FALSE.,           & !< flag parameter indicating whether the albedo may change depending on zenith
88!               force_photolysis_call = .FALSE.,     & !< flag parameter for unscheduled photolysis calls
89!               photolysis = .FALSE.,                & !< flag parameter indicating whether the photolysis model is used
90!               sun_up    = .TRUE.,                  & !< flag parameter indicating whether the sun is up or down
91!               photolysis = .TRUE.,                 & !< flag parameter indicing whether photolysis shall be calculated
92!               sun_direction = .FALSE.                !< flag parameter indicing whether solar direction shall be calculated
[2425]93
[2592]94!-- Parameters for constant photolysis frequencies
[3282]95    INTEGER,PARAMETER :: nconst  = 15               !< available predefined photolysis prequencies for constant
[2425]96
[2592]97! Names for predefined fixed photolysis frequencies at zenith angle 0
[3838]98    CHARACTER(LEN=10), PARAMETER, DIMENSION(nconst) :: names_c =  (/                     &
99                     'J_O31D    ','J_O33P    ','J_NO2     ','J_HNO3    ','J_RCHO    ',   &
100                     'J         ','J         ','J         ','J         ','J         ',   &
[2592]101                     'J         ','J         ','J         ','J         ','J         ' /)
[3838]102! Photolysis frequency at zenith angle 0 degrees in 1/s
103    REAL(wp), PARAMETER, DIMENSION(nconst) :: phot0 =  (/                                &
104                      2.489E-05_wp,3.556E-04_wp, 8.89E-03_wp,5.334E-07_wp,3.734E-05_wp,  &
105                      0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,  &
[3282]106                      0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp,0.0000E00_wp /)
[2425]107
[3838]108!-- Parameters for simple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
109!-- Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
110   INTEGER,PARAMETER :: nsimple = 15               !< available predefined photolysis prequencies for simple parameterisation
[2592]111! Names for simple photolysis frequencies parameterisation (
[3838]112    CHARACTER(LEN=10), PARAMETER, DIMENSION(nsimple) :: names_s =  (/                    &
113                     'J_O31D    ','J_O33P    ','J_H2O2    ','J_NO2     ','J_NO3_A   ',   &
114                     'J_NO3_B   ','J_HONO    ','J_HNO3    ','J_HCHO_A  ','J_HCHO_B  ',   &
[3287]115                     'J_CH3CHO  ','J         ','J         ','J         ','J_RCHO    ' /)
[2425]116
[3838]117!-- Species dependent parameters for simple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
118!-- J = l*COSx@m*EXP(-n*SECx)  with l,m,n named par_l etc., x is the zenith angle
119   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_l =  (/                                 &
120                       6.073E-05_wp,4.775E-04_wp,1.041E-05_wp,1.165E-02_wp,2.485E-02_wp, &
121                       1.747E-01_wp,2.644E-03_wp,9.312E-07_wp,4.642E-05_wp,6.853E-05_wp, &
122                       7.344E-06_wp,0.0000E00_wp,0.0000E00_wp,0.000E00_wp, 6.853E-05_wp /)
[2592]123
[3838]124   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_m =  (/                                 &
125                           1.743_wp,    0.298_wp,    0.723_wp,    0.244_wp,    0.168_wp, &
126                           0.155_wp,    0.261_wp,    1.230_wp,    0.762_wp,    0.477_wp, &
127                           1.202_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.477_wp /)
[2592]128
[3838]129   REAL(wp), PARAMETER, DIMENSION(nconst) :: par_n =  (/                                 &
130                           0.474_wp,    0.080_wp,    0.279_wp,    0.267_wp,    0.108_wp, &
131                           0.125_wp,    0.288_wp,    0.307_wp,    0.353_wp,    0.323_wp, &
132                           0.417_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.323_wp /)
[2592]133
134
[3838]135    REAL(wp)     :: cosz = 0.7_wp                   !< cosine of fixed zenith angle (45 deg, if not specified otherwise)
[2425]136
137!
138    INTERFACE photolysis_constant
139       MODULE PROCEDURE photolysis_constant
140    END INTERFACE photolysis_constant
141 
[2592]142    INTERFACE photolysis_simple
143       MODULE PROCEDURE photolysis_simple
144    END INTERFACE photolysis_simple
[2425]145!
146!   INTERFACE photolysis_fastj
147!      MODULE PROCEDURE photolysis_fastj
148!   END INTERFACE photolysis_fastj
149!
150    INTERFACE photolysis_control
151       MODULE PROCEDURE photolysis_control
152    END INTERFACE photolysis_control
153
154    SAVE
155
156    PRIVATE
157
[3282]158    PUBLIC  photolysis_control
[2592]159
[3282]160    PUBLIC  photolysis_scheme
[2425]161
162 CONTAINS
163
164
165!------------------------------------------------------------------------------!
166! Description:
167! ------------
168!> This subroutine controls the calls of the photolysis schemes
169!------------------------------------------------------------------------------!
[3838]170 SUBROUTINE photolysis_control
[2425]171 
[3838]172    IMPLICIT NONE
[2425]173
[3838]174    SELECT CASE ( TRIM( photolysis_scheme ) )
[2425]175
[3838]176       CASE ( 'constant' )
177          CALL photolysis_constant
[2425]178         
[3838]179       CASE ( 'simple' )
180          CALL photolysis_simple
[2425]181       
[3838]182!      CASE ( 'fastj' )
183!         CALL photolysis_fastj
[2425]184
[3838]185       CASE DEFAULT
[2425]186
[3838]187    END SELECT
[2425]188
189
[3838]190 END SUBROUTINE photolysis_control
[2425]191
192
193!------------------------------------------------------------------------------!
194! Description:
195! ------------
196!> This scheme keeps the prescribed net radiation constant during the run
[2656]197!> Default zenith angle is 45 deg
[2425]198!------------------------------------------------------------------------------!
[3838]199 SUBROUTINE photolysis_constant
[2425]200
[3838]201    IMPLICIT NONE
[2425]202
[3838]203    INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
[2425]204
[3838]205    DO  iphot = 1, nphot
206       DO  iav = 1, nconst
207          IF ( TRIM( names_c(iav) ) == TRIM( phot_names(iphot) ) ) THEN
208!--  Prescribe fixed photolysis frequencies  [1/s]
209                phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =                      &
[3282]210                             phot0(iav) * cosz
[3838]211          ENDIF
[2592]212       ENDDO
[3838]213    ENDDO
[2425]214
215
[3838]216 END SUBROUTINE photolysis_constant
[2656]217
[3838]218
[2592]219!------------------------------------------------------------------------------!
220! Description:
221! ------------
222!> This scheme applies a simple parameterisation for clear sky photolysis frequencies
223!> from the Master Chemical Mechanism, MCM v3.2 (http://mcm.leeds.ac.uk/MCM).
224!> Reference: Saunders et al., Atmos. Chem. Phys., 3, 161, 2003
[3838]225!> J = l*COSx@m*EXP(-n*SECx)  with l,m,n named par_l etc., x is the zenith angle
[2592]226!------------------------------------------------------------------------------!
[3838]227 SUBROUTINE photolysis_simple
[2592]228
[3838]229    USE radiation_model_mod,                                                   &
230        ONLY:  calc_zenith, cos_zenith
[3252]231
[3838]232    IMPLICIT NONE
[2592]233
[3838]234    INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
235    REAL(wp)     :: coszi     !< 1./cosine of zenith angle
[2592]236
[3838]237    DO  iphot = 1, nphot
238       phot_frequen(iphot)%freq = 0.0_wp
239    ENDDO
[2592]240
[3838]241    CALL calc_zenith
[2656]242
[3838]243    IF ( cos_zenith > 0.0_wp ) THEN
244       coszi = 1. / cos_zenith
[2656]245
[3838]246       DO iphot = 1, nphot
247          DO iav = 1, nsimple
248             IF ( TRIM( names_s(iav) ) == TRIM( phot_names(iphot) ) ) then
249                phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =                                &
250                         par_l(iav) * cos_zenith**par_m(iav) * EXP( -par_n(iav) * coszi ) 
251             ENDIF
[2425]252          ENDDO
[3838]253       ENDDO
254    ENDIF
[2828]255
[3838]256
257 END SUBROUTINE photolysis_simple
258
[2425]259 END MODULE chem_photolysis_mod
Note: See TracBrowser for help on using the repository browser.