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

Last change on this file since 4559 was 4559, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

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