source: palm/trunk/SOURCE/chem_photolysis_mod.f90

Last change on this file was 4881, checked in by forkel, 3 years ago

removed unused parameters and write statements in chemistry

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