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

Last change on this file since 3792 was 3614, checked in by raasch, 5 years ago

unused variables removed, abort renamed inifor_abort to avoid intrinsic problem in Fortran

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