source: trunk/mars/libf/aeronomars/perosat.F @ 38

Last change on this file since 38 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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