source: trunk/LMDZ.PLUTO/libf/phypluto/ch4surf.F @ 3501

Last change on this file since 3501 was 3421, checked in by afalco, 10 months ago

Pluto PCM: Added vertical mixing in no gcm, ch4/co surf, no_n2frost.
AF

File size: 4.2 KB
Line 
1      SUBROUTINE ch4surf(ngrid,nlayer,nq,ptimestep,tsurf,pdtsurf,
2     &           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
10      IMPLICIT NONE
11
12c----------------
13c   declarations:
14c   -------------
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 tsurf(ngrid)
32      REAL pplev(ngrid,nlayer+1)
33      REAL pdpsurf(ngrid)
34      REAL pq(ngrid,nlayer,nq)
35      REAL pdq(ngrid,nlayer,nq)
36      REAL pqsurf(ngrid,nq)
37      REAL pdqsurf(ngrid,nq)
38      REAL pdtsurf(ngrid)
39
40      ! Output
41      REAL pdqch4(ngrid)
42      REAL pdqsch4(ngrid)
43
44      ! local
45      REAL qsat(ngrid)
46      REAL zpsrf(ngrid)
47      REAL zq_ch4(ngrid)
48      REAL zq_n2surf(ngrid)
49      REAL ztsurf(ngrid)
50      REAL gamm(ngrid) ! activity coefficient
51      REAL rho,u,v,uv,z00,cdrag,alt
52      REAL vonk       ! Von Karman Constant
53      SAVE vonk       
54      DATA vonk/0.4/
55
56      ! Calculation of turbulent flux : F=rho*cdrag*uv*(qsat-zq)
57   
58      ! Calcul de cdrag
59      alt=5.   ! m
60      !z00=1.e-2 ! rugosity
61      z00=z0
62      cdrag=(vonk/log(alt/z00))**2
63     
64      u=6.  ! 6
65      v=3.  ! 3
66      uv=sqrt(u**2+v**2)
67       
68      pdqsch4(:)=0.     
69      pdqch4(:)=0.     
70
71      !! Update CH4, pressure
72      DO ig=1,ngrid
73          zpsrf(ig)=pplev(ig,1)
74          zq_ch4(ig)=pq(ig,1,igcm_ch4_gas)
75     &    +  pdq(ig,1,igcm_ch4_gas)*ptimestep
76          zq_n2surf(ig)=pqsurf(ig,igcm_n2)
77     &    +  pdqsurf(ig,igcm_n2)*ptimestep
78          ztsurf(ig)=tsurf(ig) !+pdtsurf(ig)*ptimestep
79      ENDDO
80
81      !! Get qsat for CH4
82      call methanesat(ngrid,ztsurf,zpsrf,qsat,zq_n2surf(:))
83
84      !! Dayfrac: Fraction of the daytime where we do not condense CH4 in N2
85          ! corresponds to cold layer of N2 pushing CH4 or depleting CH4 near the surface
86          ! By default, we do not take this into account : dayfrac=0. We condense all the time
87          ! dayfrac = 1 : we do not condense CH4 in N2 during daytime
88          ! dayfrac = 2 : all saturated, so we never condense CH4 in N2
89          ! dayfrac = 0.5 : we do not condense CH4 during half of the daytime (we condense during all night + half of daytime)
90
91      !! Loop
92      DO ig=1,ngrid
93
94         !! Take into account activity coefficient
95         gamm(ig)=499.9-21.8*ztsurf(ig)+0.249*ztsurf(ig)**2
96     &             -1.3*(zq_ch4(ig)*
97     &             mmol(igcm_n2)/mmol(igcm_ch4_gas)*100.-0.6)/0.3
98         gamm(ig)=max(gamm(ig),1.)
99         qsat(ig)=qsat(ig)*gamm(ig)
100
101         rho = zpsrf(ig) / (r *  tsurf(ig) )
102         !! Condensation Flux
103         pdqsch4(ig)=(-rho*uv*cdrag*(qsat(ig)-zq_ch4(ig)))
104
105         if (dayfrac.gt.0.and.zq_n2surf(ig).gt.thresh_non2) then
106            if (dayfrac.gt.1.) then
107               pdqsch4(ig)=min(pdqsch4(ig),0.)
108            else
109               if (pdqsch4(ig).gt.0.) then ! condensation
110                 pdqsch4(ig)=pdqsch4(ig)*(1.-fract(ig)*dayfrac)
111               endif
112            endif
113         endif
114                     
115         !! Conserve mass if reservoir depleted                   
116         if ((-pdqsch4(ig)*ptimestep).gt.
117     &                          (pqsurf(ig,igcm_ch4_ice))) then
118            pdqsch4(ig)=-pqsurf(ig,igcm_ch4_ice)/ptimestep
119         endif
120
121         if (pdqsch4(ig)*ptimestep.gt.zq_ch4(ig)*zpsrf(ig)/g) then
122            pdqsch4(ig)=zq_ch4(ig)/ptimestep*zpsrf(ig)/g
123         endif
124
125         !! Security to avoid large changes in temperatures due to
126         !latent heat                   
127         if (pdqsch4(ig)*ptimestep.gt.0.25) then
128            pdqsch4(ig)=0.25/ptimestep
129         endif
130         if (pdqsch4(ig)*ptimestep.lt.-0.25) then
131            pdqsch4(ig)=-0.25/ptimestep
132         endif
133
134         !! Atm tendency
135         pdqch4(ig)=-pdqsch4(ig)*g/zpsrf(ig)
136
137      ENDDO
138
139      RETURN
140      END
Note: See TracBrowser for help on using the repository browser.