source: trunk/LMDZ.MARS/libf/phymars/simpleclouds.F @ 520

Last change on this file since 520 was 520, checked in by tnavarro, 13 years ago

10/02/12 == TN

Major update on watercycle: a smaller integration timestep is now used

in watercloud.F, sedimentation of clouds is done in watercloud instead of
callsedim.F

Temperature-dependant contact parameter in nuclea.F
No dust lifting if CO2 ice in vdif.c
Ice integrated column opacity is written in diagfi from physiq.F, instead

of aeropacity.F. Mandatory if iradia is not 1.

New definition of permanent ice in surfini.F and possibility to have an ice

cap in it in 1d.

Update in deftank: callphys.def.outliers,run.def.1d; added traceur.def.scavenging

File size: 8.9 KB
Line 
1      subroutine simpleclouds(ngrid,nlay,ptimestep,
2     &             pplev,pplay,pzlev,pzlay,pt,pdt,
3     &             pq,pdq,pdqcloud,pdtcloud,
4     &             nq,tau,rice,nuice,rsedcloud)
5      implicit none
6c------------------------------------------------------------------
7c  This routine is used to form clouds when a parcel of the GCM is
8c    saturated. It is a simplified scheme, and there is almost no
9c    microphysics involved. When the air is saturated, water-ice
10c    clouds form on a fraction of the dust particles, specified by
11c    the constant called "ccn_factor". There is no supersaturation,
12c    and no nucleation rates computed. A more accurate scheme can
13c    be found in the routine called "improvedclouds.F".
14
15c  Modif de zq si saturation dans l'atmosphere
16c  si zq(ig,l)> zqsat(ig,l) ->    zq(ig,l)=zqsat(ig,l)
17c  Le test est effectue de bas en haut. L'eau condensee
18c    (si saturation) est remise dans la couche en dessous.
19c  L'eau condensee dans la couche du bas est deposee a la surface
20
21c  Authors: Franck Montmessin (water ice scheme)
22c           Francois Forget (changed nuclei density & outputs)
23c           Ehouarn Millour (sept.2008, tracers are now handled
24c                                   by name and not fixed index)
25c           J.-B. Madeleine (developed a single routine called
26c                            simpleclouds.F, and corrected calculations
27c                            of the typical CCN profile, Oct. 2011)
28c------------------------------------------------------------------
29#include "dimensions.h"
30#include "dimphys.h"
31#include "comcstfi.h"
32#include "callkeys.h"
33#include "tracer.h"
34#include "comgeomfi.h"
35#include "dimradmars.h"
36c------------------------------------------------------------------
37c     Arguments:
38c     ---------
39c     Inputs:
40      INTEGER ngrid,nlay
41      integer nq                 ! nombre de traceurs
42      REAL ptimestep             ! pas de temps physique (s)
43      REAL pplev(ngrid,nlay+1)   ! pression aux inter-couches (Pa)
44      REAL pplay(ngrid,nlay)     ! pression au milieu des couches (Pa)
45      REAL pzlev(ngrid,nlay+1)   ! altitude at layer boundaries
46      REAL pzlay(ngrid,nlay)     ! altitude at the middle of the layers
47      REAL pt(ngrid,nlay)        ! temperature at the middle of the
48                                 !   layers (K)
49      REAL pdt(ngrid,nlay)       ! tendance temperature des autres
50                                 !   param.
51      real pq(ngrid,nlay,nq)     ! traceur (kg/kg)
52      real pdq(ngrid,nlay,nq)    ! tendance avant condensation
53                                 !   (kg/kg.s-1)
54      REAL tau(ngridmx,naerkind) ! Column dust optical depth at each point
55
56c     Output:
57      REAL rice(ngrid,nlay)      ! Ice mass mean radius (m)
58                                 ! (r_c in montmessin_2004)
59      REAL nuice(ngrid,nlay)     ! Estimated effective variance
60                                 !   of the size distribution
61      real rsedcloud(ngridmx,nlayermx) ! Cloud sedimentation radius
62      real pdqcloud(ngrid,nlay,nq) ! tendance de la condensation
63                                   !   H2O(kg/kg.s-1)
64      REAL pdtcloud(ngrid,nlay)    ! tendance temperature due
65                                   !   a la chaleur latente
66
67c------------------------------------------------------------------
68c     Local variables:
69
70      LOGICAL firstcall
71      DATA firstcall/.true./
72      SAVE firstcall
73
74      REAL CBRT
75      EXTERNAL CBRT
76
77      INTEGER ig,l
78
79      REAL zq(ngridmx,nlayermx,nqmx)  ! local value of tracers
80      REAL zq0(ngridmx,nlayermx,nqmx) ! local initial value of tracers
81      REAL zt(ngridmx,nlayermx)       ! local value of temperature
82      REAL zqsat(ngridmx,nlayermx)    ! saturation
83      REAL*8 dzq                      ! masse de glace echangee (kg/kg)
84      REAL lw                         !Latent heat of sublimation (J.kg-1)
85      REAL,PARAMETER :: To=273.15     ! reference temperature, T=273.15 K
86      real rdusttyp(ngridmx,nlayermx) ! Typical dust geom. mean radius (m)
87      REAL ccntyp(ngridmx,nlayermx)
88                                      ! Typical dust number density (#/kg)
89c     CCN reduction factor
90c      REAL, PARAMETER :: ccn_factor = 4.5  !! comme TESTS_JB // 1. avant
91     
92      REAL Mcon_out(ngridmx,nlayermx) ! mass to be condensed (not dMice !!)
93
94c-----------------------------------------------------------------------
95c    1. initialisation
96c    -----------------
97
98c    On "update" la valeur de q(nqmx) (water vapor) et temperature.
99c    On effectue qqes calculs preliminaires sur les couches :
100
101      do l=1,nlay
102        do ig=1,ngrid
103          zq(ig,l,igcm_h2o_vap)=
104     &      pq(ig,l,igcm_h2o_vap)+pdq(ig,l,igcm_h2o_vap)*ptimestep
105          zq(ig,l,igcm_h2o_vap)=max(zq(ig,l,igcm_h2o_vap),1.E-30) ! FF 12/2004
106          zq0(ig,l,igcm_h2o_vap)=zq(ig,l,igcm_h2o_vap)
107          zt(ig,l)=pt(ig,l)+ pdt(ig,l)*ptimestep
108
109          zq(ig,l,igcm_h2o_ice)=
110     &      pq(ig,l,igcm_h2o_ice)+pdq(ig,l,igcm_h2o_ice)*ptimestep
111          zq(ig,l,igcm_h2o_ice)=max(zq(ig,l,igcm_h2o_ice),0.) ! FF 12/2004
112          zq0(ig,l,igcm_h2o_ice)=zq(ig,l,igcm_h2o_ice)
113        enddo
114      enddo
115
116      do l=1,nlay
117        do ig=1,ngrid
118
119c         Typical dust radius profile:
120          rdusttyp(ig,l)= max(.8e-6*exp(-pzlay(ig,l)/18000.),1.e-9)
121
122c         Typical CCN profile:
123c         Corrected equation, following Montmessin et al. 2004
124c           (N0=2e6 m-3 has been converted into N0=1.3e8 kg-1, otherwise
125c            the equation for rice is not homogeneous...)
126          ccntyp(ig,l)=
127     &       1.3e+8*max(tau(ig,1),0.001)/0.1*exp(-pzlay(ig,l)/10000.)
128c         The previously used profile was not correct:
129c         ccntyp(ig,l)=( epaisseur(ig,l)/masse(ig,l) ) *
130c    &       2.e+6/0.1*max(tau(ig,1),0.001)*exp(-pzlay(ig,l)/10000.)
131
132c         Reduce number of nuclei
133!         TEMPORAIRE : decrease the number of CCNs FF 04/200
134!         reduction facteur 3
135!         ccntyp(ig,l) = ccntyp(ig,l) / 27.
136!         reduction facteur 2
137!         ccntyp(ig,l) = ccntyp(ig,l) / 8.
138c -----------------------------------------------------------------
139          ccntyp(ig,l) = ccntyp(ig,l) / ccn_factor
140
141        enddo ! of do ig=1,ngrid
142      enddo ! of do l=1,nlay
143
144      pdqcloud(1:ngrid,1:nlay,1:nq)=0
145      pdtcloud(1:ngrid,1:nlay)=0
146
147c     ----------------------------------------------
148c
149c
150c     Rapport de melange a saturation dans la couche l : -------
151c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
152
153      call watersat(ngridmx*nlayermx,zt,pplay,zqsat)
154
155c     taux de condensation (kg/kg/s-1) dans les differentes couches
156c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
157
158      do l=1,nlay
159        do ig=1,ngrid
160
161          if (zq(ig,l,igcm_h2o_vap).ge.zqsat(ig,l))then  !  Condensation
162            dzq=zq(ig,l,igcm_h2o_vap)-zqsat(ig,l)               
163          elseif(zq(ig,l,igcm_h2o_vap).lt.zqsat(ig,l))then  ! Sublimation
164            dzq=-min(zqsat(ig,l)-zq(ig,l,igcm_h2o_vap),
165     &               zq(ig,l,igcm_h2o_ice))
166          endif
167
168c         Water Mass change
169c         ~~~~~~~~~~~~~~~~~
170          zq(ig,l,igcm_h2o_ice)=zq(ig,l,igcm_h2o_ice)+dzq
171          zq(ig,l,igcm_h2o_vap)=zq(ig,l,igcm_h2o_vap)-dzq
172         
173          Mcon_out(ig,l) = dzq
174
175c         Calcul du rayon moyen des particules de glace.
176c         Hypothese : Dans une couche, la glace presente se
177c         repartit uniformement autour du nbre de poussieres
178c         dont le rayon moyen est prescrit par rdusttyp.
179c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
180          rice(ig,l)=max( CBRT ( (zq(ig,l,igcm_h2o_ice)/rho_ice
181     &      +ccntyp(ig,l)*(4./3.)*pi*rdusttyp(ig,l)**3.)
182     &      /(ccntyp(ig,l)*4./3.*pi) ), rdusttyp(ig,l))
183c         Effective variance of the size distribution
184          nuice(ig,l)=nuice_ref
185
186c         Sedimentation radius:
187c         ~~~~~~~~~~~~~~~~~~~~
188
189          rsedcloud(ig,l)=max( rice(ig,l)*(1.+nuice_sed)**3.,
190     &                         rdusttyp(ig,l) )
191          rsedcloud(ig,l)=min(rsedcloud(ig,l),1.e-4)
192
193        enddo ! of do ig=1,ngrid
194      enddo ! of do l=1,nlay
195
196c     Tendance finale
197c     ~~~~~~~~~~~~~~~
198      do l=1, nlay
199        do ig=1,ngridmx
200          pdqcloud(ig,l,igcm_h2o_vap)=(zq(ig,l,igcm_h2o_vap)
201     &                            -zq0(ig,l,igcm_h2o_vap))/ptimestep
202          pdqcloud(ig,l,igcm_h2o_ice) =
203     &      (zq(ig,l,igcm_h2o_ice) - zq0(ig,l,igcm_h2o_ice))/ptimestep
204          lw=(2834.3-0.28*(zt(ig,l)-To)-0.004*(zt(ig,l)-To)**2)*1.e+3
205          pdtcloud(ig,l)=-pdqcloud(ig,l,igcm_h2o_vap)*lw/cpp
206        end do
207      end do
208
209c------------------------------------------------------------------
210c     TEST_JBM
211!      IF (ngrid.eq.1) THEN
212!         call WRITEDIAGFI(ngrid,"mcond","h2o condensed mass","kg",1,
213!     &                    Mcon_out)
214!         call WRITEDIAGFI(ngrid,"rdusttyp","rdusttyp","m",1,
215!     &                    rdusttyp)
216!         call WRITEDIAGFI(ngrid,"ccntyp","ccntyp","kg-1",1,
217!     &                    ccntyp)
218!      ENDIF
219c------------------------------------------------------------------
220      return
221      end
Note: See TracBrowser for help on using the repository browser.