source: trunk/LMDZ.MARS/libf/aeronomars/perosat.F

Last change on this file was 3466, checked in by emillour, 2 months ago

Mars PCM:
More tidying in aeronomars:

  • remove unused "inv.F" and remove "dtridgl.F" which is not used here and is a duplicate of the "dtridgl" routine in phymars/swr_toon.F
  • turn aeronomars routines to modules, for those which aren't in modules yet.

EM

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