/[lmdze]/trunk/phylmd/ozonecm.f90
ViewVC logotype

Diff of /trunk/phylmd/ozonecm.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 98 by guez, Tue May 13 17:23:16 2014 UTC revision 316 by guez, Tue Dec 11 12:59:24 2018 UTC
# Line 16  contains Line 16  contains
16      ! also provided us the code.      ! also provided us the code.
17    
18      ! A. J. Krueger and R. A. Minzner, A Mid-Latitude Ozone Model for the      ! A. J. Krueger and R. A. Minzner, A Mid-Latitude Ozone Model for the
19      ! 1976 U.S. Standard Atmosphere, J. Geophys. Res., 81, 4477, (1976).      ! 1976 U. S. Standard Atmosphere, J. Geophys. Res., 81, 4477 (1976).
20    
21      ! Keating, G. M. and D. F. Young, 1985: Interim reference models for the      ! Keating, G. M. and D. F. Young, 1985: Interim reference ozone
22      ! middle atmosphere, Handbook for MAP, vol. 16, 205-229.      ! models for the middle atmosphere, Handbook for MAP, vol. 16,
23        ! 205-229.
24    
25      use dimens_m, only: llm      use nr_util, only: assert, twopi, deg_to_rad
26      USE dimphy, ONLY : klon  
27      use nr_util, only: assert, pi      use dimensions, only: llm
28      use phyetat0_m, only: rlat      use phyetat0_m, only: rlat
29    
30      REAL, INTENT (IN) :: rjour      REAL, INTENT (IN) :: rjour
     REAL, INTENT (IN) :: paprs(:, :) ! (klon, llm+1)  
31    
32      REAL ozonecm(klon, llm)      REAL, INTENT (IN) :: paprs(:, :) ! (klon, llm + 1)
33        ! pression pour chaque inter-couche, en Pa
34    
35        REAL ozonecm(size(paprs, 1), llm) ! (klon, llm)
36      ! "ozonecm(j, k)" is the column-density of ozone in cell "(j, k)", that is      ! "ozonecm(j, k)" is the column-density of ozone in cell "(j, k)", that is
37      ! between interface "k" and interface "k + 1", in kDU.      ! between interface "k" and interface "k + 1", in kDU.
38    
39      ! Local:      ! Local:
40    
41      REAL tozon, pl      REAL tozon ! equivalent pressure of ozone above interface "k", in Pa
42      INTEGER i, k      INTEGER i, k
43    
44      REAL field(klon, llm+1)      REAL field(llm + 1)
45      ! "field(:, k)" is the column-density of ozone between interface      ! "field(k)" is the column-density of ozone between interface
46      ! "k" and the top of the atmosphere (interface "llm + 1"), in kDU.      ! "k" and the top of the atmosphere (interface "llm + 1"), in kDU.
47    
48      real, PARAMETER:: ps=101325.      real, PARAMETER:: ps = 101325.
49      REAL, parameter:: an = 360., unit = 2.1415E-5, zo3q3 = 4E-8      REAL, parameter:: an = 360., zo3q3 = 4E-8
50      REAL gms, zslat, zsint, zcost, z, ppm, qpm, a      real, parameter:: zo3a3 = zo3q3 / ps / 2.
51      REAL asec, bsec, aprim, zo3a3      REAL, parameter:: dobson_unit = 2.1415E-5 ! in kg m-2
52        REAL gms, slat, slat2, sint, cost, ppm, a
53        REAL asec, bsec, aprim
54    
55      !----------------------------------------------------------      !----------------------------------------------------------
56    
57      call assert(shape(paprs) == (/klon, llm + 1/), "ozonecm")      call assert(size(paprs, 2) == llm + 1, "ozonecm")
58    
59      DO k = 1, llm      sint = sin(twopi * (rjour + 15.) / an)
60         DO i = 1, klon      cost = cos(twopi * (rjour + 15.) / an)
61            zslat = sin(pi / 180. * rlat(i))      field(llm + 1) = 0.
62            zsint = sin(2.*pi*(rjour+15.)/an)  
63            zcost = cos(2.*pi*(rjour+15.)/an)      DO i = 1, size(paprs, 1)
64            z = 0.0531 + zsint * (-0.001595+0.009443*zslat) &         slat = sin(deg_to_rad * rlat(i))
65                 + zcost * (-0.001344-0.00346*zslat) &         slat2 = slat * slat
66                 + zslat**2 * (.056222 + zslat**2 &         gms = 0.0531 + sint * (- 0.001595 + 0.009443 * slat) + cost &
67                 * (-.037609+.012248*zsint+.00521*zcost+.008890*zslat))              * (- 0.001344 - 0.00346 * slat) + slat2 * (0.056222 + slat2 &
68            zo3a3 = zo3q3/ps/2.              * (- 0.037609 + 0.012248 * sint + 0.00521 * cost + 0.00889 &
69            z = z - zo3q3*ps              * slat)) - zo3q3 * ps
70            gms = z         ppm = 800. - 500. * slat2 - 150. * cost * slat
71            ppm = 800. - (500.*zslat+150.*zcost)*zslat         bsec = 2650. + 5000. * slat2
72            qpm = 1.74E-5 - (7.5E-6*zslat+1.7E-6*zcost)*zslat         a = 4. * bsec**1.5 * ppm**1.5 * (1. + (bsec / ps)**1.5) &
73            bsec = 2650. + 5000.*zslat**2              / (bsec**1.5 + ppm**1.5)**2
74            a = 4.0*(bsec)**(3./2.)*(ppm)**(3./2.)*(1.0+(bsec/ps)**(3./2.))         asec = max(0., (gms - max(0., (2.666666 * (1.74E-5 - 7.5E-6 * slat2 &
75            a = a/(bsec**(3./2.)+ppm**(3./2.))**2              - 1.7E-6 * cost * slat) * ppm - a * gms) / (1. - a))) &
76            aprim = (2.666666*qpm*ppm-a*gms)/(1.0-a)              * (1. + (bsec / ps)**1.5))
77            aprim = amax1(0., aprim)         aprim = gms - asec / (1. + (bsec / ps)**1.5)
78            asec = (gms-aprim)*(1.0+(bsec/ps)**(3./2.))  
79            asec = amax1(0.0, asec)         DO k = 1, llm
80            aprim = gms - asec/(1.+(bsec/ps)**(3./2.))            tozon = aprim / (1. + 3. * (ppm / paprs(i, k))**2) &
81            pl = paprs(i, k)                 + asec / (1. + (bsec / paprs(i, k))**1.5) &
82            tozon = aprim / (1. + 3. * (ppm / pl)**2) &                 + zo3a3 * paprs(i, k) * paprs(i, k)
                + asec / (1. + (bsec / pl)**(3./2.)) + zo3a3 * pl * pl  
83            ! Convert from Pa to kDU:            ! Convert from Pa to kDU:
84            field(i, k) = tozon / 9.81 / unit / 1e3            field(k) = tozon / 9.81 / dobson_unit / 1e3
85         END DO         END DO
86    
87           forall (k = 1: llm) ozonecm(i, k) = field(k) - field(k + 1)
88      END DO      END DO
89    
90      field(:, llm+1) = 0.      ozonecm = max(ozonecm, 1e-12)
     forall (k = 1: llm) ozonecm(:, k) = field(:, k) - field(:, k+1)  
91    
92    END function ozonecm    END function ozonecm
93    

Legend:
Removed from v.98  
changed lines
  Added in v.316

  ViewVC Help
Powered by ViewVC 1.1.21