1 | SUBROUTINE ch4surf(ngrid,nlayer,nq,ptimestep,capcal,tsurf, |
---|
2 | & pdtsurf,pplev,pdpsurf,pq,pdq,pqsurf,pdqsurf,pdqch4,pdqsch4) |
---|
3 | |
---|
4 | use callkeys_mod, only: dayfrac, thresh_non2 |
---|
5 | use comcstfi_mod, only: g, r |
---|
6 | use comgeomfi_h |
---|
7 | use comsaison_h, only: fract |
---|
8 | use planete_mod, only: z0 |
---|
9 | use tracer_h, only: igcm_ch4_gas,igcm_ch4_ice,igcm_n2,mmol,lw_ch4 |
---|
10 | IMPLICIT NONE |
---|
11 | |
---|
12 | c---------------- |
---|
13 | c declarations: |
---|
14 | c ------------- |
---|
15 | |
---|
16 | #include "dimensions.h" |
---|
17 | |
---|
18 | ! Routine for nogcm : sublimation/condensation scheme at the surface |
---|
19 | ! Output : tendancy for methane mixing ratio and surface reservoir : |
---|
20 | ! pdqch4, pdqs_ch4 |
---|
21 | |
---|
22 | !----------------------------------------------------------------------- |
---|
23 | ! Arguments |
---|
24 | |
---|
25 | |
---|
26 | INTEGER ngrid,nlayer,nq |
---|
27 | REAL ptimestep |
---|
28 | INTEGER ig,iq |
---|
29 | |
---|
30 | ! input : |
---|
31 | REAL capcal(ngrid) ! surface heat capacity (J m-2 K-1) |
---|
32 | REAL tsurf(ngrid) |
---|
33 | REAL pplev(ngrid,nlayer+1) |
---|
34 | REAL pdpsurf(ngrid) |
---|
35 | REAL pq(ngrid,nlayer,nq) |
---|
36 | REAL pdq(ngrid,nlayer,nq) |
---|
37 | REAL pqsurf(ngrid,nq) |
---|
38 | REAL pdqsurf(ngrid,nq) |
---|
39 | REAL pdtsurf(ngrid) |
---|
40 | |
---|
41 | ! Output |
---|
42 | REAL pdqch4(ngrid) |
---|
43 | REAL pdqsch4(ngrid) |
---|
44 | |
---|
45 | ! local |
---|
46 | REAL qsat(ngrid) |
---|
47 | REAL zpsrf(ngrid) |
---|
48 | REAL zq_ch4(ngrid) |
---|
49 | REAL zq_n2surf(ngrid) |
---|
50 | REAL ztsurf(ngrid) |
---|
51 | REAL gamm(ngrid) ! activity coefficient |
---|
52 | REAL rho,u,v,uv,z00,cdrag,alt |
---|
53 | REAL vonk ! Von Karman Constant |
---|
54 | SAVE vonk |
---|
55 | DATA vonk/0.4/ |
---|
56 | |
---|
57 | ! Calculation of turbulent flux : F=rho*cdrag*uv*(qsat-zq) |
---|
58 | |
---|
59 | ! Calcul de cdrag |
---|
60 | alt=5. ! m |
---|
61 | !z00=1.e-2 ! rugosity |
---|
62 | z00=z0 |
---|
63 | cdrag=(vonk/log(alt/z00))**2 |
---|
64 | |
---|
65 | u=0.3 ! 6 |
---|
66 | v=0.4 ! 3 |
---|
67 | uv=sqrt(u**2+v**2) |
---|
68 | |
---|
69 | pdqsch4(:)=0. |
---|
70 | pdqch4(:)=0. |
---|
71 | |
---|
72 | !! Update CH4, pressure |
---|
73 | DO ig=1,ngrid |
---|
74 | zpsrf(ig)=pplev(ig,1) |
---|
75 | zq_ch4(ig)=pq(ig,1,igcm_ch4_gas) |
---|
76 | & + pdq(ig,1,igcm_ch4_gas)*ptimestep |
---|
77 | zq_n2surf(ig)=pqsurf(ig,igcm_n2) |
---|
78 | & + pdqsurf(ig,igcm_n2)*ptimestep |
---|
79 | ztsurf(ig)=tsurf(ig) !+pdtsurf(ig)*ptimestep |
---|
80 | ENDDO |
---|
81 | |
---|
82 | !! Get qsat for CH4 |
---|
83 | call methanesat(ngrid,ztsurf,zpsrf,qsat,zq_n2surf(:)) |
---|
84 | |
---|
85 | !! Dayfrac: Fraction of the daytime where we do not condense CH4 in N2 |
---|
86 | ! corresponds to cold layer of N2 pushing CH4 or depleting CH4 near the surface |
---|
87 | ! By default, we do not take this into account : dayfrac=0. We condense all the time |
---|
88 | ! dayfrac = 1 : we do not condense CH4 in N2 during daytime |
---|
89 | ! dayfrac = 2 : all saturated, so we never condense CH4 in N2 |
---|
90 | ! dayfrac = 0.5 : we do not condense CH4 during half of the daytime (we condense during all night + half of daytime) |
---|
91 | |
---|
92 | !! Loop |
---|
93 | DO ig=1,ngrid |
---|
94 | |
---|
95 | !! Take into account activity coefficient |
---|
96 | gamm(ig)=499.9-21.8*ztsurf(ig)+0.249*ztsurf(ig)**2 |
---|
97 | & -1.3*(zq_ch4(ig)* |
---|
98 | & mmol(igcm_n2)/mmol(igcm_ch4_gas)*100.-0.6)/0.3 |
---|
99 | gamm(ig)=max(gamm(ig),1.) |
---|
100 | !qsat(ig)=qsat(ig)*gamm(ig) |
---|
101 | |
---|
102 | rho = zpsrf(ig) / (r * tsurf(ig) ) |
---|
103 | !! Condensation Flux |
---|
104 | pdqsch4(ig)=(-rho*uv*cdrag*(qsat(ig)-zq_ch4(ig))) |
---|
105 | |
---|
106 | if (dayfrac.gt.0.and.zq_n2surf(ig).gt.thresh_non2) then |
---|
107 | if (dayfrac.gt.1.) then |
---|
108 | pdqsch4(ig)=min(pdqsch4(ig),0.) |
---|
109 | else |
---|
110 | if (pdqsch4(ig).gt.0.) then ! condensation |
---|
111 | pdqsch4(ig)=pdqsch4(ig)*(1.-fract(ig)*dayfrac) |
---|
112 | endif |
---|
113 | endif |
---|
114 | endif |
---|
115 | |
---|
116 | !! Conserve mass if reservoir depleted |
---|
117 | if ((-pdqsch4(ig)*ptimestep).gt. |
---|
118 | & (pqsurf(ig,igcm_ch4_ice))) then |
---|
119 | pdqsch4(ig)=-pqsurf(ig,igcm_ch4_ice)/ptimestep |
---|
120 | endif |
---|
121 | |
---|
122 | if (pdqsch4(ig)*ptimestep.gt.zq_ch4(ig)*zpsrf(ig)/g) then |
---|
123 | pdqsch4(ig)=zq_ch4(ig)/ptimestep*zpsrf(ig)/g |
---|
124 | endif |
---|
125 | |
---|
126 | !! Security to avoid large changes in temperatures due to |
---|
127 | !latent heat |
---|
128 | if (lw_ch4*pdqsch4(ig)*ptimestep/capcal(ig).gt.1.) then |
---|
129 | pdqsch4(ig)=1./(lw_ch4*ptimestep)*capcal(ig) |
---|
130 | endif |
---|
131 | if (lw_ch4*pdqsch4(ig)*ptimestep/capcal(ig).lt.-1.) then |
---|
132 | pdqsch4(ig)=-1./(lw_ch4*ptimestep)*capcal(ig) |
---|
133 | endif |
---|
134 | !if (pdqsch4(ig)*ptimestep.gt.0.25) then |
---|
135 | ! pdqsch4(ig)=0.25/ptimestep |
---|
136 | !endif |
---|
137 | !if (pdqsch4(ig)*ptimestep.lt.-0.25) then |
---|
138 | ! pdqsch4(ig)=-0.25/ptimestep |
---|
139 | !endif |
---|
140 | |
---|
141 | !! Atm tendency |
---|
142 | pdqch4(ig)=-pdqsch4(ig)*g/zpsrf(ig) |
---|
143 | |
---|
144 | ENDDO |
---|
145 | |
---|
146 | RETURN |
---|
147 | END |
---|