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

Last change on this file since 2808 was 2615, checked in by romain.vande, 3 years ago

LMDZ_MARS RV : Open_MP;
Put all the "save" variables as "!$OMP THREADPRIVATE" in aeronomars

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