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

Last change on this file since 1448 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

  • Optimized computations in paramfoto_compact (twice less dlog10 calculations)
  • Checked consistency before/after modification in debug mode
  • Checked performance is not impacted (same as before)
File size: 4.6 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
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 ig
35      REAL ptimestep                ! pas de temps physique (s)
36      REAL pplev(ngrid,nlayer+1)    ! pression aux inter-couches (Pa)
37      REAL pplay(ngrid,nlayer)      ! pression au milieu des couches (Pa)
38      REAL zt(nlayer)               ! temperature au centre des couches (K)
39                                    ! deja mise a jour dans calchim
40
41c   Traceurs :
42      real zy(nlayer,nq)        ! traceur (fraction molaire sortie chimie)
43      real pdqcloud(ngrid,nlayer,nq) ! tendance condensation (kg/kg.s-1)
44      real 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
57c     Pour diagnostique :
58c     ~~~~~~~~~~~~~~~~~
59      REAL taucond(ngrid,nlayer)   ! 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,nlayer
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, nlayer
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=nlayer,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, nlayer
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.