source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/aeronomars/perosat.F @ 3574

Last change on this file since 3574 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 4.3 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(i_h2o2)   
16c=======================================================================
17
18c-----------------------------------------------------------------------
19c   declarations:
20c   -------------
21
22#include "dimensions.h"
23#include "dimphys.h"
24#include "comcstfi.h"
25#include "chimiedata.h"
26#include "tracer.h"
27#include "conc.h"
28c
29c   arguments:
30c   ----------
31
32      INTEGER ig
33      REAL ptimestep                ! pas de temps physique (s)
34      REAL pplev(ngridmx,nlayermx+1)! pression aux inter-couches (Pa)
35      REAL pplay(ngridmx,nlayermx)  ! pression au milieu des couches (Pa)
36      REAL zt(nlayermx)             ! temperature au centre des couches (K)
37                                    ! deja mise a jour dans calchim
38
39c   Traceurs :
40      real zy(nlayermx,nqmx)        ! traceur (fraction molaire sortie chimie)
41      real pdqcloud(ngridmx,nlayermx,nqmx) ! tendance condensation (kg/kg.s-1)
42      real pdqscloud(ngridmx,nqmx)         ! flux en surface (kg.m-2.s-1)
43     
44c   local:
45c   ------
46
47      INTEGER l,iq
48      INTEGER i_h2o2
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
55c     Pour diagnostique :
56c     ~~~~~~~~~~~~~~~~~
57      REAL taucond(ngridmx,nlayermx)   ! taux de condensation (kg/kg/s-1)
58
59c-----------------------------------------------------------------------
60c    1. initialisation
61c    -----------------
62c
63      do iq=1,nqmx
64       if (noms(iq).eq."h2o2") then
65          i_h2o2 = iq
66c         print *,'H2O2: ',noms(iq),' iq=',iq
67c      else
68c         print *,noms(iq),' iq=',iq
69       endif
70      enddo
71
72c    ----------------------------------------------
73c   
74c       Rapport de melange a saturation dans la couche l :
75c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
76c
77c       d'apres Lindner, Planet. Space Sci., 36, 125, 1988.
78c       domaine d'application: T < 220 K
79c
80        do l = 1,nlayermx
81
82c       print *,'ig=',ig,' l=',l,' i_h2o2=',i_h2o2
83c       print *,'y=',zy(l,i_h2o2),' T=',zt(l)
84
85             zynew(l) = zy(l,i_h2o2)
86
87             if (zt(l) .le. 220.) then
88               psat_hg = 10.**(11.98 - (3422./zt(l)))
89               psat_hpa = psat_hg*760./1013.
90               zysat(l) = (psat_hpa*100./pplay(ig,l))
91             else
92               zysat(l) = 1.e+30
93             end if
94
95c       print *,'ysat=',zysat(l)
96
97        end do
98
99c       taux de condensation (kg/kg/s-1) dans les differentes couches
100c       ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
101c       (Pour diagnostic seulement !)
102c
103        do l=1, nlayermx
104            taucond(ig,l)= max((zy(l,i_h2o2)-zysat(l))*mmol(i_h2o2)
105     $                         /(mmean(ig,l)*ptimestep),0.)
106        end do
107c
108c       Saturation couche nlay a 2 : 
109c       ~~~~~~~~~~~~~~~~~~~~~~~~~~
110c
111        do l=nlayermx,2, -1
112           if (zynew(l).gt.zysat(l)) then
113              zynew(l-1) =  zynew(l-1) + (zynew(l) - zysat(l))
114     &      *(pplev(ig,l)-pplev(ig,l+1))/(pplev(ig,l-1)-pplev(ig,l))
115
116              zynew(l)=zysat(l)
117           endif
118        enddo
119c
120c       Saturation couche l=1
121c       ~~~~~~~~~~~~~~~~~~~~~
122c
123        if (zynew(1).gt.zysat(1)) then
124           pdqscloud(ig,i_h2o2)= (zynew(1)-zysat(1))*mmol(i_h2o2)
125     $   *(pplev(ig,1)-pplev(ig,2))/(mmean(ig,1)*g*ptimestep)
126c
127           zynew(1)=zysat(1)
128        end if
129c
130c       Tendance finale
131c       ~~~~~~~~~~~~~~~
132c
133        do l=1, nlayermx
134           pdqcloud(ig,l,i_h2o2)=(zynew(l) - zy(l,i_h2o2))*mmol(i_h2o2)
135     &                           /(mmean(ig,l)*ptimestep)
136c          print *,'pdqcloud=',pdqcloud(ig,l,i_h2o2)
137        end do
138
139      RETURN
140      END
Note: See TracBrowser for help on using the repository browser.