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

Last change on this file since 3294 was 3274, checked in by knoop, 6 years ago

Modularization of all bulk cloud physics code components

  • Property svn:keywords set to Id
File size: 13.1 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 1997-2018 Leibniz Universitaet Hannover
18! Copyright 2017-2018 Karlsruhe Institute of Technology
19!------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: chem_photolysis_mod.f90 3274 2018-09-24 15:42:55Z raasch $
28! Modularization of all bulk cloud physics code components
29!
30! 3241 2018-09-12 15:02:00Z raasch
31! unused variables commented
32!
33! 2766 2018-01-22 17:17:47Z kanani
34! Removed preprocessor directive __chem
35!
36! 2718 2018-01-02 08:49:38Z maronga
37! Initial revision
38!
39!
40! Authors:
41! --------
42! @author Renate Forkel
43!
44!------------------------------------------------------------------------------!
45! Description:
46! ------------
47!> photolysis models and interfaces (Adapted from photolysis_model_mod.f90)
48!> @todo Alles!
49!------------------------------------------------------------------------------!
50 MODULE chem_photolysis_mod
51
52    USE arrays_3d,                                                             &
53        ONLY:  dzw, hyp, pt, q, ql, zu, zw
54
55    USE basic_constants_and_equations_mod,                                     &
56        ONLY:  pi
57
58    USE control_parameters,                                                    &
59        ONLY:  time_since_reference_point
60
61    USE pegrid,             ONLY: myid, threads_per_task
62
63    USE indices,                                                               &
64        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
65
66    USE radiation_model_mod,                                                   &
67        ONLY:  calc_zenith, zenith
68               !day, day_init, lat, lambda, lon,                   &
69               !time_utc, time_utc_init,    !FKa: This is now handled by date_and_time_mod
70
71    USE control_parameters,                                                    &
72        ONLY:  initializing_actions           
73!       ONLY:  cloud_droplets, initializing_actions,                           &
74!              large_scale_forcing, lsf_surf, phi, pt_surface, rho_surface,    &
75!              surface_pressure, time_since_reference_point
76
77    USE chem_gasphase_mod,                                                     &
78        ONLY: nphot, phot_names, phot 
79
80    USE chemistry_model_mod,                                                   &
81        ONLY: phot_frequen, photolysis_scheme
82
83    USE chem_modules,                                                          &
84        ONLY: chem_debug2
85
86!   REAL(wp), DIMENSION(0:0) ::  zenith,         & !< cosine of solar zenith angle
87!                                sun_dir_lat,    & !< solar directional vector in latitudes
88!                                sun_dir_lon       !< solar directional vector in longitudes
89    USE kinds
90
91#if defined ( __netcdf )
92    USE NETCDF
93#endif
94
95
96    IMPLICIT NONE
97
98
99!   LOGICAL ::  unscheduled_photolysis_calls = .TRUE., & !< flag parameter indicating whether additional calls of the photolysis code are allowed
100!               constant_albedo = .FALSE.,           & !< flag parameter indicating whether the albedo may change depending on zenith
101!               force_photolysis_call = .FALSE.,     & !< flag parameter for unscheduled photolysis calls
102!               photolysis = .FALSE.,                & !< flag parameter indicating whether the photolysis model is used
103!               sun_up    = .TRUE.,                  & !< flag parameter indicating whether the sun is up or down
104!               photolysis = .TRUE.,                 & !< flag parameter indicing whether photolysis shall be calculated
105!               sun_direction = .FALSE.                !< flag parameter indicing whether solar direction shall be calculated
106
107!-- Parameters for constant photolysis frequencies
108     INTEGER,PARAMETER :: nconst  = 15               !< available predefined photolysis prequencies for constant
109
110! Names for predefined fixed photolysis frequencies at zenith angle 0
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         ', &
114                     'J         ','J         ','J         ','J         ','J         ' /)
115! Photolysis frequency at zenith angle 0 in 1/s
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 /)
120
121
122!-- Parameters for simple photolysis frequencies
123     INTEGER,PARAMETER :: nsimple = 15               !< available predefined photolysis prequencies for simpel 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  ', &
128                     'J_CH3CHO  ','J         ','J         ','J         ','J_RCHO    ' /)
129
130!-- Parameters for simeple photolysis frequencies from MCM (http://mcm.leeds.ac.uk/MCM)
131!-- Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
132     REAL(wp), PARAMETER, DIMENSION(nconst) :: par_l =  (/                             &
133                     6.073E-05_wp,4.775E-04_wp,1.041E-05_wp,1.165E-02_wp,2.485E-02_wp, &
134                     1.747E-01_wp,2.644E-03_wp,9.312E-07_wp,4.642E-05_wp,6.853E-05_wp, &
135                     7.344E-06_wp,0.0000E00_wp,0.0000E00_wp,0.000E00_wp, 6.853E-05_wp /)
136
137     REAL(wp), PARAMETER, DIMENSION(nconst) :: par_m =  (/                             &
138                         1.743_wp,    0.298_wp,    0.723_wp,    0.244_wp,    0.168_wp, &
139                         0.155_wp,    0.261_wp,    1.230_wp,    0.762_wp,    0.477_wp, &
140                         1.202_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.477_wp /)
141
142     REAL(wp), PARAMETER, DIMENSION(nconst) :: par_n =  (/                             &
143                         0.474_wp,    0.080_wp,    0.279_wp,    0.267_wp,    0.108_wp, &
144                         0.125_wp,    0.288_wp,    0.307_wp,    0.353_wp,    0.323_wp, &
145                         0.417_wp,    0.000_wp,    0.000_wp,    0.000_wp,    0.323_wp /)
146
147
148!    REAL(wp) :: time_photolysis = 0.0_wp,         & !< time since last call of photolysis code
149!                dt_photolysis = 0.0_wp,           & !< hotolysis model timestep
150!                skip_time_do_photolysis = 0.0_wp    !< Radiation model is not called before this time
151
152    REAL(wp)     :: cosz = 0.7_wp                   !< cosine of Zenith angle (45 deg, if not specified otherwise)
153
154!
155!-- Variables and parameters used in Fast-J only
156! ....
157
158!   INTERFACE photolysis_check_parameters
159!      MODULE PROCEDURE photolysis_check_parameters
160!   END INTERFACE photolysis_check_parameters
161 
162    INTERFACE photolysis_constant
163       MODULE PROCEDURE photolysis_constant
164    END INTERFACE photolysis_constant
165 
166    INTERFACE photolysis_simple
167       MODULE PROCEDURE photolysis_simple
168    END INTERFACE photolysis_simple
169!
170!   INTERFACE photolysis_fastj
171!      MODULE PROCEDURE photolysis_fastj
172!   END INTERFACE photolysis_fastj
173!
174    INTERFACE photolysis_control
175       MODULE PROCEDURE photolysis_control
176    END INTERFACE photolysis_control
177
178!   INTERFACE photolysis_header
179!      MODULE PROCEDURE photolysis_header
180!   END INTERFACE photolysis_header
181!
182    INTERFACE photolysis_init
183       MODULE PROCEDURE photolysis_init
184    END INTERFACE photolysis_init
185
186!   INTERFACE photolysis_parin
187!      MODULE PROCEDURE photolysis_parin
188!   END INTERFACE photolysis_parin
189   
190!   INTERFACE photolysis_read_restart_data
191!      MODULE PROCEDURE photolysis_read_restart_data
192!   END INTERFACE photolysis_read_restart_data
193
194!   INTERFACE photolysis_last_actions
195!      MODULE PROCEDURE photolysis_last_actions
196!   END INTERFACE photolysis_last_actions
197
198    SAVE
199
200    PRIVATE
201
202!
203!-- Public functions / NEEDS SORTING
204!   PUBLIC photolysis_init
205!          photolysis_check_parameters, photolysis_control,                      &
206!          photolysis_header, photolysis_init, photolysis_parin !,                 &
207!          photolysis_define_netcdf_grid, photolysis_last_actions,               &
208!          photolysis_read_restart_data, photolysis_data_output_mask
209
210   PUBLIC  photolysis_control, photolysis_init
211
212   PUBLIC  photolysis_scheme
213!
214
215 CONTAINS
216
217
218!------------------------------------------------------------------------------!
219! Description:
220! ------------
221!> This subroutine controls the calls of the photolysis schemes
222!------------------------------------------------------------------------------!
223    SUBROUTINE photolysis_control
224 
225 
226       IMPLICIT NONE
227
228
229       SELECT CASE ( TRIM( photolysis_scheme ) )
230
231          CASE ( 'constant' )
232             CALL photolysis_constant
233         
234          CASE ( 'simple' )
235             CALL photolysis_simple
236       
237!         CASE ( 'fastj' )
238!            CALL photolysis_fastj
239
240          CASE DEFAULT
241
242       END SELECT
243
244
245    END SUBROUTINE photolysis_control
246
247!------------------------------------------------------------------------------!
248! Description:
249! ------------
250!> Initialization of the photolysis model
251!------------------------------------------------------------------------------!
252    SUBROUTINE photolysis_init    !### not yes used. Call should be placed near call of chem_init
253   
254       IMPLICIT NONE
255
256!-- Just in case we need anything
257
258       RETURN
259
260    END SUBROUTINE photolysis_init
261
262
263!------------------------------------------------------------------------------!
264! Description:
265! ------------
266!> This scheme keeps the prescribed net radiation constant during the run
267!> Default zenith angle is 45 deg
268!------------------------------------------------------------------------------!
269    SUBROUTINE photolysis_constant
270
271
272       IMPLICIT NONE
273
274!      INTEGER(iwp) :: i, j, k   !< loop indices
275       INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
276!      REAL(wp)     :: exn,   &  !< Exner functions at surface (better use palms own exner array in arrays_3d)
277!                      pt1       !< potential temperature at first grid level
278
279       DO iphot = 1,nphot
280          DO iav = 1,nconst
281             IF ( TRIM( names_c(iav) ) == TRIM( phot_names(iphot) ) ) then
282!--    Prescribe fixed photolysis frequencies  [1/s]
283!             IF(myid == 0 .AND. chem_debug2 )  WRITE(06,*) iphot, iav,phot_names(iphot),names_c(iav)
284
285                      phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =    &
286                            phot0(iav) * cosz
287
288!              IF(myid == 0 .AND. chem_debug2 )  WRITE(06,*) phot_frequen(iphot)%freq(1,5,5)
289            ENDIF
290          ENDDO
291       ENDDO
292
293    END SUBROUTINE photolysis_constant
294
295
296!------------------------------------------------------------------------------!
297! Description:
298! ------------
299!> This scheme applies a simple parameterisation for clear sky photolysis frequencies
300!> from the Master Chemical Mechanism, MCM v3.2 (http://mcm.leeds.ac.uk/MCM).
301!> Reference: Saunders et al., Atmos. Chem. Phys., 3, 161, 2003
302!------------------------------------------------------------------------------!
303    SUBROUTINE photolysis_simple
304
305       IMPLICIT NONE
306
307!      INTEGER(iwp) :: i, j, k   !< loop indices
308       INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
309!      REAL(wp)     :: exn,   &  !< Exner functions at surface (better use palms own exner array in arrays_3d)
310!                      pt1       !< potential temperature at first grid level
311       REAL(wp)     :: coszi     !< 1./cosine of zenith angle
312
313    DO iphot = 1,nphot
314       phot_frequen(iphot)%freq = 0.0_wp
315    ENDDO
316
317    CALL calc_zenith
318
319    IF ( zenith(0) > 0.0_wp ) THEN
320       coszi = 1. / zenith(0)
321
322       DO iphot = 1,nphot
323          DO iav = 1,nsimple
324             IF ( TRIM( names_s(iav) ) == TRIM( phot_names(iphot) ) ) then
325!              if(myid == 0 .AND. chem_debug2 )  WRITE(06,*) 'simple', iphot, iav,phot_names(iphot),names_s(iav)
326
327                      phot_frequen(iphot)%freq(nzb+1:nzt,:,:) =    &
328                            par_l(iav) * zenith(0)**par_m(iav) *  EXP( -par_n(iav) * coszi ) 
329
330!              if(myid == 0 .AND. chem_debug2 )  WRITE(06,*) 'simple', phot_frequen(iphot)%freq(1,5,5)
331            ENDIF
332          ENDDO
333       ENDDO
334    ENDIF
335
336    END SUBROUTINE photolysis_simple
337
338 END MODULE chem_photolysis_mod
Note: See TracBrowser for help on using the repository browser.