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

Last change on this file since 1036 was 1036, checked in by emillour, 11 years ago

Mars GCM: (a first step towards using parallel dynamics)

  • IMPORTANT CHANGE: Implemented dynamic tracers. It is no longer necessary to compile the model with the '-t #' option, number of tracers is simply read from tracer.def file (as before). Adapted makegcm_* scripts (and co.) accordingly. Technical aspects of the switch to dynamic tracers are:
    • advtrac.h (in dyn3d) removed and replaced by module infotrac.F
    • tracer.h (in phymars) removed and replaced by module tracer_mod.F90 (which contains nqmx, the number of tracers, etc. and can be used anywhere in the physics).
  • Included some side cleanups: removed unused files (in dyn3d) anldoppler2.F, anl_mcdstats.F and anl_stats-diag.F, and all the unecessary dimensions.* files in grid/dimension.
  • Checked that changes are clean and that GCM yields identical results (in debug mode) to previous svn version.

EM

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