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

Last change on this file since 3577 was 3298, checked in by kanani, 6 years ago

Merge chemistry branch at r3297 to trunk

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