source: flexpart.git/src/photo_O1D.f90 @ 4c64400

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 4c64400 was 5f9d14a, checked in by Espen Sollum ATMOS <eso@…>, 9 years ago

Updated wet depo scheme

  • Property mode set to 100644
File size: 3.8 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22real function photo_O1D(sza)
23
24  !*****************************************************************************
25  !                                                                            *
26  !                                                                            *
27  !    Author: A. Stohl                                                        *
28  !                                                                            *
29  !    Nov 2014                                                                *
30  !                                                                            *
31  !                                                                            *
32  !*****************************************************************************
33  !                                                                            *
34  !    INPUT:                                                                  *
35  !    sza        solar zenith angle (degrees)                                 *
36  !                                                                            *
37  !    OUTPUT:                                                                 *
38  !    photo_O1D  J(O1D) photoylsis rate                                       *
39  !                                                                            *
40  !*****************************************************************************
41
42  implicit none
43
44  integer :: iz,ik
45  real :: sza
46  real :: z1,z2,zg,f1,f2,dummy
47  real :: photo_NO2
48  integer, parameter :: nzenith=11
49  real, parameter :: pi=3.1415927
50  real, dimension(nzenith) :: zangle,fact_photo
51
52  ! zangle: zenith angles for which fact_photo is tabulated
53  ! fact_photo: conversion of photolysis rate of NO2 to photolysis
54  !     rate of O3 into O1D as a function of solar zenith angle
55
56  zangle=(/0.,10.,20.,30.,40.,50.,60.,70.,78.,86.,90.0001/)
57  fact_photo=(/0.4616E-02,0.4478E-02,0.4131E-02,0.3583E-02,0.2867E-02,&
58    &0.2081E-02,0.1235E-02,0.5392E-03,0.2200E-03,0.1302E-03,0.0902E-03/)
59
60  if (sza.lt.90.) then
61    do iz=1,nzenith-1
62      if(sza.ge.zangle(iz)) ik=iz
63    end do
64    z1=1./cos(zangle(ik)*pi/180.)
65    z2=1./cos(zangle(ik+1)*pi/180.)
66    zg=1./cos(sza*pi/180.)
67    dummy=(zg-z1)/(z2-z1)
68    f1=alog(fact_photo(ik))
69    f2=alog(fact_photo(ik+1))
70    photo_NO2=1.45e-2*exp(-0.4/cos(sza*pi/180.))
71    photo_O1D=photo_NO2*exp(f1+(f2-f1)*dummy)
72  else
73    photo_O1D=0.
74  endif
75
76  return
77
78end function photo_O1D
79
80
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG