1 | SUBROUTINE perosat(ngrid,nlayer,nq,ig, ptimestep, |
---|
2 | $ pplev, pplay, zt, |
---|
3 | & zy, pdqcloud, pdqscloud) |
---|
4 | |
---|
5 | use tracer_mod, only: igcm_h2o2, mmol |
---|
6 | use conc_mod, only: mmean |
---|
7 | IMPLICIT NONE |
---|
8 | |
---|
9 | c======================================================================= |
---|
10 | c Treatment of saturation of hydrogen peroxide (H2O2) |
---|
11 | c |
---|
12 | c Modif de zq si saturation dans l'atmopshere |
---|
13 | c si zq(ig,l)> zqsat(ig,l) -> zq(ig,l)=zqsat(ig,l) |
---|
14 | c Le test est effectue de bas en haut. H2O2 condense |
---|
15 | c (si saturation) est remis dans la couche en dessous. |
---|
16 | c H2O2 condense dans la couche du bas est depose a la surface |
---|
17 | c |
---|
18 | c WARNING : H2O2 mixing ratio is assumed to be q(igcm_h2o2) |
---|
19 | c index igcm_h2o2 is known from tracer_mod |
---|
20 | c======================================================================= |
---|
21 | |
---|
22 | c----------------------------------------------------------------------- |
---|
23 | c declarations: |
---|
24 | c ------------- |
---|
25 | |
---|
26 | !#include "dimensions.h" |
---|
27 | !#include "dimphys.h" |
---|
28 | #include "comcstfi.h" |
---|
29 | !#include "chimiedata.h" |
---|
30 | !#include "tracer.h" |
---|
31 | !#include "conc.h" |
---|
32 | c |
---|
33 | c arguments: |
---|
34 | c ---------- |
---|
35 | |
---|
36 | integer,intent(in) :: ngrid ! number of atmospheric columns |
---|
37 | integer,intent(in) :: nlayer ! number of atmospheric layers |
---|
38 | integer,intent(in) :: nq ! number of tracers |
---|
39 | INTEGER ig |
---|
40 | REAL ptimestep ! pas de temps physique (s) |
---|
41 | REAL pplev(ngrid,nlayer+1) ! pression aux inter-couches (Pa) |
---|
42 | REAL pplay(ngrid,nlayer) ! pression au milieu des couches (Pa) |
---|
43 | REAL zt(nlayer) ! temperature au centre des couches (K) |
---|
44 | ! deja mise a jour dans calchim |
---|
45 | |
---|
46 | c Traceurs : |
---|
47 | real zy(nlayer,nq) ! traceur (fraction molaire sortie chimie) |
---|
48 | real pdqcloud(ngrid,nlayer,nq) ! tendance condensation (kg/kg.s-1) |
---|
49 | real pdqscloud(ngrid,nq) ! flux en surface (kg.m-2.s-1) |
---|
50 | |
---|
51 | c local: |
---|
52 | c ------ |
---|
53 | |
---|
54 | INTEGER l,iq |
---|
55 | |
---|
56 | REAL zysat(nlayer) |
---|
57 | REAL zynew(nlayer) ! mole fraction after condensation |
---|
58 | REAL psat_hg ! pression saturante (mm Hg) |
---|
59 | REAL psat_hpa ! pression saturante (hPa) |
---|
60 | logical,save :: firstcall=.true. |
---|
61 | |
---|
62 | c Pour diagnostique : |
---|
63 | c ~~~~~~~~~~~~~~~~~ |
---|
64 | REAL taucond(ngrid,nlayer) ! taux de condensation (kg/kg/s-1) |
---|
65 | |
---|
66 | c----------------------------------------------------------------------- |
---|
67 | c 1. initialisation/verification |
---|
68 | c ------------------------------ |
---|
69 | c |
---|
70 | if (firstcall) then |
---|
71 | ! check that there is an h2o2 tracer: |
---|
72 | if (igcm_h2o2.eq.0) then |
---|
73 | write(*,*) "perosat: error; no h2o2 tracer !!!!" |
---|
74 | stop |
---|
75 | endif |
---|
76 | firstcall=.false. |
---|
77 | endif |
---|
78 | |
---|
79 | c ---------------------------------------------- |
---|
80 | c |
---|
81 | c Rapport de melange a saturation dans la couche l : |
---|
82 | c ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
83 | c |
---|
84 | c d'apres Lindner, Planet. Space Sci., 36, 125, 1988. |
---|
85 | c domaine d'application: T < 220 K |
---|
86 | c |
---|
87 | do l = 1,nlayer |
---|
88 | |
---|
89 | c print *,'ig=',ig,' l=',l,' igcm_h2o2=',igcm_h2o2 |
---|
90 | c print *,'y=',zy(l,igcm_h2o2),' T=',zt(l) |
---|
91 | |
---|
92 | zynew(l) = zy(l,igcm_h2o2) |
---|
93 | |
---|
94 | if (zt(l) .le. 220.) then |
---|
95 | psat_hg = 10.**(11.98 - (3422./zt(l))) |
---|
96 | psat_hpa = psat_hg*760./1013. |
---|
97 | zysat(l) = (psat_hpa*100./pplay(ig,l)) |
---|
98 | else |
---|
99 | zysat(l) = 1.e+30 |
---|
100 | end if |
---|
101 | |
---|
102 | c print *,'ysat=',zysat(l) |
---|
103 | |
---|
104 | end do |
---|
105 | |
---|
106 | c taux de condensation (kg/kg/s-1) dans les differentes couches |
---|
107 | c ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
108 | c (Pour diagnostic seulement !) |
---|
109 | c |
---|
110 | do l=1, nlayer |
---|
111 | taucond(ig,l)=max((zy(l,igcm_h2o2)-zysat(l))*mmol(igcm_h2o2) |
---|
112 | $ /(mmean(ig,l)*ptimestep),0.) |
---|
113 | end do |
---|
114 | c |
---|
115 | c Saturation couche nlay a 2 : |
---|
116 | c ~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
117 | c |
---|
118 | do l=nlayer,2, -1 |
---|
119 | if (zynew(l).gt.zysat(l)) then |
---|
120 | zynew(l-1) = zynew(l-1) + (zynew(l) - zysat(l)) |
---|
121 | & *(pplev(ig,l)-pplev(ig,l+1))/(pplev(ig,l-1)-pplev(ig,l)) |
---|
122 | |
---|
123 | zynew(l)=zysat(l) |
---|
124 | endif |
---|
125 | enddo |
---|
126 | c |
---|
127 | c Saturation couche l=1 |
---|
128 | c ~~~~~~~~~~~~~~~~~~~~~ |
---|
129 | c |
---|
130 | if (zynew(1).gt.zysat(1)) then |
---|
131 | pdqscloud(ig,igcm_h2o2)= (zynew(1)-zysat(1))*mmol(igcm_h2o2) |
---|
132 | $ *(pplev(ig,1)-pplev(ig,2))/(mmean(ig,1)*g*ptimestep) |
---|
133 | c |
---|
134 | zynew(1)=zysat(1) |
---|
135 | else |
---|
136 | pdqscloud(ig,igcm_h2o2)=0 |
---|
137 | end if |
---|
138 | c |
---|
139 | c Tendance finale |
---|
140 | c ~~~~~~~~~~~~~~~ |
---|
141 | c |
---|
142 | do l=1, nlayer |
---|
143 | pdqcloud(ig,l,igcm_h2o2)=(zynew(l) - zy(l,igcm_h2o2)) |
---|
144 | & *mmol(igcm_h2o2)/(mmean(ig,l)*ptimestep) |
---|
145 | c print *,'pdqcloud=',pdqcloud(ig,l,igcm_h2o2) |
---|
146 | end do |
---|
147 | |
---|
148 | RETURN |
---|
149 | END |
---|