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

Last change on this file since 3992 was 3876, checked in by knoop, 5 years ago

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

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