source: trunk/LMDZ.PLUTO.old/libf/phypluto/ch4cloud.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 11.9 KB
Line 
1       SUBROUTINE ch4cloud(ngrid,nlay,naersize, ptimestep,
2     &                pplev,pplay,pdpsrf,pzlev,pzlay,pt,pdt,
3     &                pq,pdq,pdqcloud,pdqscloud,pdtcloud,
4     &                nq,rice_ch4)
5
6      use comgeomfi_h     
7      IMPLICIT NONE
8
9c=======================================================================
10c     Treatment of saturation of METHANE
11c
12c
13c     Modif de zq si saturation dans l'atmosphere
14c     si zq(ig,l)> zqsat(ig,l) ->    zq(ig,l)=zqsat(ig,l)
15c     Le test est effectue de bas en haut. CH4 condensee
16c    (si saturation) est remise dans la couche en dessous.
17c     Le methane condensee dans la couche du bas est deposee a la surface
18c       
19c     Melanie Vangvichith (adapted from Mars water clouds)
20c     Tanguy Bertrand
21c     Completely rewritten by Francois Forget (to properly estimate the
22c               latent heat release.
23c
24c=======================================================================
25
26c-----------------------------------------------------------------------
27c   declarations:
28c   -------------
29
30#include "dimensions.h"
31#include "dimphys.h"
32#include "comcstfi.h"
33#include "callkeys.h"
34#include "tracer.h"
35
36c   Inputs:
37c   ------
38
39      INTEGER ngrid,nlay
40      REAL ptimestep             ! pas de temps physique (s)
41      REAL pplev(ngrid,nlay+1)   ! pression aux inter-couches (Pa)
42      REAL pplay(ngrid,nlay)     ! pression au milieu des couches (Pa)
43      REAL pdpsrf(ngrid)         ! tendance surf pressure
44      REAL pzlev(ngrid,nlay+1)   ! altitude at layer boundaries
45      REAL pzlay(ngrid,nlay)     ! altitude at the middle of the layers
46      REAL pt(ngrid,nlay)        ! temperature at the middle of the layers (K)
47      REAL pdt(ngrid,nlay)       ! tendance temperature des autres param.
48
49      real pq(ngrid,nlay,nq)     ! traceur (kg/kg)
50      real pdq(ngrid,nlay,nq)    ! tendance avant condensation  (kg/kg.s-1)
51      integer naersize   ! nombre de traceurs radiativement actifs (=naerkind)
52      integer nq         ! nombre de traceurs
53
54c   Outputs:
55c   -------
56
57      real pdqcloud(ngrid,nlay,nq) ! tendance de la condensation CH4(kg/kg.s-1)
58      real pdqscloud(ngrid,nq)     ! flux en surface (kg.m-2.s-1)
59      REAL pdtcloud(ngrid,nlay)    ! tendance temperature due
60                                   !   a la chaleur latente
61      REAL rice_ch4(ngrid,nlay)    ! CH4 Ice mass mean radius (m)
62                               ! (r_c in montmessin_2004)
63   
64c   local:
65c   ------
66c      REAL Nmix   ! Cloud condensation nuclei
67c      parameter (Nmix=1.E5)  ! /kg
68      real rnuclei  ! Nuclei geometric mean radius (m)
69      parameter (rnuclei=2.E-7)  ! m
70
71      REAL CBRT
72      EXTERNAL CBRT
73      INTEGER ig,l
74
75
76      REAL zq(ngridmx,nlayermx,nqmx)  ! local value of tracers
77      REAL zqsat(ngridmx,nlayermx)    ! saturation
78      REAL zt(ngridmx,nlayermx)       ! local value of temperature
79
80      REAL vecnull(ngridmx*nlayermx)
81   
82      LOGICAL,SAVE :: firstcall=.true.
83
84! indexes of methane gas, methane ice and dust tracers:
85      INTEGER,SAVE :: i_ch4=0  ! methane gas
86      INTEGER,SAVE :: i_ice=0  ! methane ice
87
88      REAL Tfin,qch4_fin
89      REAL temp_fin ! function used to compute Tfin at the end of the timestep
90
91c     TEMPORAIRE :
92
93      real  pdtcloudmax,pdtcloudmin
94      integer  igmin, igmax,lmin,lmax
95
96
97
98c    ** un petit test de coherence
99c       --------------------------
100
101      IF (firstcall) THEN
102        IF(ngrid.NE.ngridmx) THEN
103            PRINT*,'STOP dans ch4cloud'
104            PRINT*,'probleme de dimensions :'
105            PRINT*,'ngrid  =',ngrid
106            PRINT*,'ngridmx  =',ngridmx
107            STOP
108        ENDIF
109         
110        if (nq.gt.nqmx) then
111           write(*,*) 'stop in ch4cloud (nq.gt.nqmx)!'
112           write(*,*) 'nq=',nq,' nqmx=',nqmx
113           stop
114        endif
115         
116        i_ch4=igcm_ch4_gas
117        i_ice=igcm_ch4_ice
118       
119        write(*,*) "methanecloud: i_ch4=",i_ch4
120        write(*,*) "            i_ice=",i_ice
121
122        firstcall=.false.
123      ENDIF ! of IF (firstcall)
124
125
126c-----------------------------------------------------------------------
127c    1. initialisation
128c    -----------------
129
130c    On "update" la valeur de q(nqmx) (methane vapor) et temperature.
131c    On effectue qqes calculs preliminaires sur les couches :
132
133      do l=1,nlay
134        do ig=1,ngrid
135          zt(ig,l)=pt(ig,l)+ pdt(ig,l)*ptimestep
136          zq(ig,l,i_ch4)=pq(ig,l,i_ch4)+pdq(ig,l,i_ch4)*ptimestep
137          zq(ig,l,i_ch4)=max(zq(ig,l,i_ch4),1.E-30)
138          zq(ig,l,i_ice)=pq(ig,l,i_ice)+pdq(ig,l,i_ice)*ptimestep
139          zq(ig,l,i_ice)=max(zq(ig,l,i_ice),0.)
140        enddo
141      enddo
142
143      pdqscloud(1:ngrid,1:nq)=0
144      pdqcloud(1:ngrid,1:nlay,1:nq)=0
145      pdtcloud(1:ngrid,1:nlay)=0
146
147c    ----------------------------------------------
148c
149c
150c       q à saturation dans la couche l à temperature prédite zt
151c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
152         call methanesat(ngridmx*nlayermx,zt,pplay,zqsat,vecnull)
153
154
155c       Loop to work where CH4 condensation/sublimation is occuring
156c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
157        do l=1,nlay
158          do ig=1,ngrid
159             if ((zq(ig,l,i_ch4).gt.zqsat(ig,l)).or.
160     &       (zq(ig,l,i_ice).gt.1.E-10) ) then ! phase change
161
162               if(zq(ig,l,i_ice).lt.(zqsat(ig,l)-zq(ig,l,i_ch4))) then
163                 !case when everything is sublimed:
164                 qch4_fin = zq(ig,l,i_ch4) + zq(ig,l,i_ice) 
165                 Tfin = zt(ig,l) - (qch4_fin-zq(ig,l,i_ch4))*lw_ch4/cpp
166               else 
167                 !case when CH4 ice is present at the end
168                 qch4_fin = zqsat(ig,l)
169                 Tfin = zt(ig,l) - (qch4_fin-zq(ig,l,i_ch4))*lw_ch4/cpp
170                 if(abs(Tfin-zt(ig,l)).gt.1.) then   
171!                  Improved calculation if the temperature change is significant (1K?)
172
173c                  Estimating the temperature Tfin and condensation at the end of the
174c                  timestep due to condensation-sublimation process, taking into acount
175c                  latent heat, given by:   Tfin - zt = (zq - qsat(Tfin))*L/cp
176c                  Tfin, solution, of the equation, is estimated by iteration
177c                  We assume that improved Tfin is between zt and the 1st estimation of Tfin:
178                   Tfin = temp_fin(zt(ig,l),Tfin,0.01,pplay(ig,l),
179     &             zt(ig,l),zq(ig,l,i_ch4),qch4_fin)
180c                  Security check for small changes
181                   if(abs(zq(ig,l,i_ch4)-qch4_fin).gt.
182     &                abs(zq(ig,l,i_ch4)- zqsat(ig,l))  ) then
183                      write(*,*) "warning: inaccuracy in CH4 clouds"
184                      write(*,*) 'zq(ig,l,i_ch4),qch4_fin, zqsat(ig,l)',
185     &                zq(ig,l,i_ch4),qch4_fin, zqsat(ig,l)
186
187                      qch4_fin = zqsat(ig,l)
188
189                   end if
190                 end if
191               end if
192c              Final tendancies
193               pdqcloud(ig,l,i_ch4)=(qch4_fin-zq(ig,l,i_ch4))/ptimestep
194
195               !TB16
196               IF (zq(ig,l,i_ch4)+pdqcloud(ig,l,i_ch4)*ptimestep.lt.0.)
197     &                                                 then
198                  pdqcloud(ig,l,i_ch4)=-zq(ig,l,i_ch4)/ptimestep
199               END IF   
200
201               pdqcloud(ig,l,i_ice) = - pdqcloud(ig,l,i_ch4)
202               pdtcloud(ig,l)=(Tfin - zt(ig,l))/ptimestep
203
204c               Ice particle radius
205                zq(ig,l,i_ice)=
206     &            zq(ig,l,i_ice)+pdqcloud(ig,l,i_ice)*ptimestep
207                rice_ch4(ig,l)=max( CBRT ( (zq(ig,l,i_ice)/rho_ch4_ice
208     &          +Nmix_ch4*(4./3.)*pi*rnuclei**3.)/(Nmix_ch4*4./3.*pi)),
209     &                                        rnuclei)   
210             end if
211            enddo ! of do ig=1,ngrid
212          enddo ! of do l=1,nlay
213
214c       A correction if a lot of subliming N2 fills the 1st layer FF04/2005
215c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
216c       Then that should not affect the ice particle radius
217        do ig=1,ngridmx
218          if(pdpsrf(ig)*ptimestep.gt.0.9*(pplev(ig,1)-pplev(ig,2)))then
219            if(pdpsrf(ig)*ptimestep.gt.0.9*(pplev(ig,1)-pplev(ig,3)))
220     &      rice_ch4(ig,2)=rice_ch4(ig,3)
221            rice_ch4(ig,1)=rice_ch4(ig,2)
222          end if
223        end do
224
225c************ ANALYSE pour Icarus ****************
226c
227c        pdtcloudmax =0.
228c        pdtcloudmin =0.
229c        igmin=999
230c        igmax=999
231c        lmin =999
232c        lmax =999
233c        do l=1, nlay
234c          do ig=1,ngridmx
235c            if(pdtcloud(ig,l).gt.pdtcloudmax) then
236c               igmax=ig
237c               lmax = l
238c               pdtcloudmax=pdtcloud(ig,l)
239c            else if(pdtcloud(ig,l).lt.pdtcloudmin) then
240c               igmin=ig
241c               lmin = l
242c               pdtcloudmin=pdtcloud(ig,l)
243c            end if
244c          end do
245c        end do
246c
247c        write(*,*)
248c        write(*,*) "MAX , ig, l, Tbefore, Tafter, Tfin_ini"
249c        write(*,*) igmax,lmax, zt(igmax,lmax),
250c    &      zt(igmax,lmax)+ pdtcloud(igmax,lmax)*ptimestep,
251c    &zt(igmax,lmax)-(zqsat(igmax,lmax)-zq(igmax,lmax,i_ch4))*lw_ch4/cpp
252c        write(*,*) "MAX ,  Qch4gas_before, Qch4gas_after, Qsat ini"
253c       write(*,*) pq(igmax,lmax,i_ch4)+pdq(igmax,lmax,i_ch4)*ptimestep,
254c    &   pq(igmax,lmax,i_ch4)+
255c    &   (pdq(igmax,lmax,i_ch4)+ pdqcloud(igmax,lmax,i_ch4))*ptimestep
256c    &    ,zqsat(igmax,lmax)
257c        write(*,*) "MAX ,  Qch4ice_before, Qch4ice_after"
258c       write(*,*) pq(igmax,lmax,i_ice)+pdq(igmax,lmax,i_ice)*ptimestep,
259c    &   pq(igmax,lmax,i_ice)+
260c    &   (pdq(igmax,lmax,i_ice)+ pdqcloud(igmax,lmax,i_ice))*ptimestep
261c        write(*,*) 'Rice=',  rice_ch4(igmax,lmax)
262c
263c        write(*,*)
264c        write(*,*) "MIN , ig, l, Tbefore, Tafter, Tfin_ini"
265c        write(*,*) igmin,lmin, zt(igmin,lmin),
266c    &             zt(igmin,lmin)+ pdtcloud(igmin,lmin)*ptimestep,
267c    &zt(igmin,lmin)-(zqsat(igmin,lmin)-zq(igmin,lmin,i_ch4))*lw_ch4/cpp
268c        write(*,*) "MIN ,  Qch4gas_before, Qch4gas_after, Qsat ini"
269c       write(*,*) pq(igmin,lmin,i_ch4)+pdq(igmin,lmin,i_ch4)*ptimestep,
270c    &   pq(igmin,lmin,i_ch4)+
271c    &   (pdq(igmin,lmin,i_ch4)+ pdqcloud(igmin,lmin,i_ch4))*ptimestep
272c    &    ,zqsat(igmin,lmin)
273c        write(*,*) "MIN ,  Qch4ice_before, Qch4ice_after"
274c       write(*,*) pq(igmin,lmin,i_ice)+pdq(igmin,lmin,i_ice)*ptimestep,
275c    &   pq(igmin,lmin,i_ice)+
276c    &   (pdq(igmin,lmin,i_ice)+ pdqcloud(igmin,lmin,i_ice))*ptimestep
277c        write(*,*) 'Rice=',  rice_ch4(igmin,lmin)
278c        write(*,*) "pdtcloud(igmin,lmin) " , pdtcloud(igmin,lmin)
279c        write(*,*) "pdqcloud(i_ch4)", pdqcloud(igmin,lmin,i_ch4)
280c        write(*,*) "pdqcloud(i_ice)", pdqcloud(igmin,lmin,i_ice)
281c
282 
283c************ FIN ANALYSE pour Icarus ****************
284       
285c**************************************************
286c       Output --- removed
287c**************************************************
288! NB: for diagnostics use zq(), the updated value of tracers
289c         Computing ext visible optical depth  in each layer
290
291      RETURN
292      END
293
294!================================================================================
295
296      FUNCTION temp_fin(X1,X2,XACC,pres,temp,zq,qsat)
297       implicit none
298#include "dimensions.h"
299#include "dimphys.h"
300#include "comcstfi.h"
301#include "tracer.h"
302       real pres, temp, zq,qsat
303       real X1,X2,XACC, F
304       real FMID,D,temp_fin,DX, XMID
305       integer JMAX,J
306       real func
307
308      PARAMETER (JMAX=40)
309
310      call methanesat(1,X2,pres,qsat,0.)
311      FMID = X2 -temp -(zq-qsat)*lw_ch4/cpp
312
313      call methanesat(1,X1,pres,qsat,0.)
314      F = X1 -temp -(zq-qsat)*lw_ch4/cpp
315
316      IF(F*FMID.GE.0.) write(*,*)  'Fix Tfin firt guesses in ch4cloud'
317      IF(F.LT.0.)THEN
318        temp_fin=X1
319        DX=X2-X1
320      ELSE
321        temp_fin=X2
322        DX=X1-X2
323      ENDIF
324      DO 11 J=1,JMAX
325        DX=DX*.5
326        XMID=temp_fin+DX
327
328        call methanesat(1,XMID,pres,qsat,0.)
329        FMID = XMID -temp -(zq-qsat)*lw_ch4/cpp
330
331        IF(FMID.LE.0.)temp_fin=XMID
332        IF(ABS(DX).LT.XACC .OR. FMID.EQ.0.) RETURN
33311    CONTINUE
334!     PAUSE 'too many bisections'
335      END
336
337 
Note: See TracBrowser for help on using the repository browser.