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

Last change on this file since 358 was 358, checked in by aslmd, 13 years ago

LMDZ.MARS:


A FIRST VERSION WITH SCAVENGING
TRANSPARENT TO CASUAL USER
FOR WATER CYCLE FOLKS, SEE BELOW


[TN and AS solved conflicts due to r330 >> r357]


07/11/11 == JBM

Changed watercloud.F to call two separate routines,

simpleclouds.F or improvedclouds.F, which are a simplified and
full microphysical scheme for cloud formation, respectively.
Removed the tag called "improved" in watercloud.F, and added
another tag called "microphys" which is defined in callphys.F
instead. Changed routines: callkeys, inifis, physiq, watercloud.

Reimplemented the use of typical profiles of dust particle sizes

and CCNs in simpleclouds.F. Corrected the previously used
analytical CCN profile. Moved ccn_factor to simpleclouds.F,
which won't be used in the new microphysical scheme. Changed
routines: aeropacity, physiq, simpleclouds, watercloud.

Computed rdust at the end of callsedim instead of updatereffrad,

except at firstcall. Renamed rfall into rsedcloud and moved it
in simpleclouds. Moved nuice_sed to initracer.F and added it to
tracer.h. Changed routines: callsedim, physiq, tracer.h,
watercloud, initracer, simpleclouds, updatereffrad.

Added two tracers for the CCNs. Added the different tests in

initracer.F to make sure that, for example, microphys is not
used without doubleq, etc. Corrected an inconsistency in
callsedim.F, and changed the way r0 is updated. Changes
routines: callsedim, inifis, initracer, physiq, testphys1d,
tracer.h.

Added the ability to have a spatially variable density in

newsedim (same method as that used for the radius of
sedimentation). Required the addition of one input to newsedim,
which is the size of the density variable "rho". Changed
routines: callsedim, newsedim.

Added an output to aeropacity called "tauscaling", which is a

factor to convert dust_mass and dust_number to true quantities,
based on tauvis. Removed ccn and qdust from aeropacity, which
are obsolete now.

Wrote improvedcloud.F which includes all the microphysical

scheme, and connected it to the sedimentation scheme. Added and
changed routines: callsedim, physiq, growthrate, nuclea,
improvedclouds, initracer, watercloud, microphys.h.

07/11/11 == TN

Added CCN & dust tracers updates in physiq.F

Corrected a bug that can give negative CCN numbers, due to the
use of single precision values (only 6 decimals) whereas up to 10E+10
CCN can be formed or disappears...

Corrected physical bug that causes h2o_vap or h2o_ice

to be negative in improvedclouds.F.

Corrected physical bug that causes CCN & dust tracers

to be negative in improvedclouds.F when all ice sublimates and
releases dust

Added parameter contact mteta in callphys.def

Default value is still 0.95, see inifis.F

Changed tendancy computation for dust_number in improvedclouds.F

that was not the right one. Indeed, the scavenged dust_number tracer
is computed from the dust_mass one, and its tendancy before scavenging
must be taken into account to compute its scavenging's tendancy.

File size: 9.3 KB
Line 
1      subroutine simpleclouds(ngrid,nlay,ptimestep,
2     &             pplev,pplay,pzlev,pzlay,pt,pdt,
3     &             pq,pdq,pdqcloud,pdqscloud,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 pdqscloud(ngrid,nq)     ! flux en surface (kg.m-2.s-1)
65      REAL pdtcloud(ngrid,nlay)    ! tendance temperature due
66                                   !   a la chaleur latente
67
68c------------------------------------------------------------------
69c     Local variables:
70
71      LOGICAL firstcall
72      DATA firstcall/.true./
73      SAVE firstcall
74
75      REAL CBRT
76      EXTERNAL CBRT
77
78      INTEGER ig,l
79
80      REAL zq(ngridmx,nlayermx,nqmx)  ! local value of tracers
81      REAL zq0(ngridmx,nlayermx,nqmx) ! local initial value of tracers
82      REAL zt(ngridmx,nlayermx)       ! local value of temperature
83      REAL zqsat(ngridmx,nlayermx)    ! saturation
84      REAL*8 dzq                      ! masse de glace echangee (kg/kg)
85      REAL lw                         !Latent heat of sublimation (J.kg-1)
86      REAL,PARAMETER :: To=273.15     ! reference temperature, T=273.15 K
87      real rdusttyp(ngridmx,nlayermx) ! Typical dust geom. mean radius (m)
88      REAL ccntyp(ngridmx,nlayermx)
89                                      ! Typical dust number density (#/kg)
90c     CCN reduction factor
91      REAL, PARAMETER :: ccn_factor = 4.5  !! comme TESTS_JB // 1. avant
92     
93      REAL Mcon_out(ngridmx,nlayermx) ! mass to be condensed (not dMice !!)
94
95
96c------------------------------------------------------------------
97
98c     Write ccn_factor;
99      IF (firstcall) THEN
100        write(*,*) "water_param CCN reduc. fac. ", ccn_factor
101        write(*,*) "Careful: only used when microphys=F, otherwise"
102        write(*,*) "  the contact parameter is used instead;"
103        firstcall=.false.
104      END IF
105
106c-----------------------------------------------------------------------
107c    1. initialisation
108c    -----------------
109
110c    On "update" la valeur de q(nqmx) (water vapor) et temperature.
111c    On effectue qqes calculs preliminaires sur les couches :
112
113      do l=1,nlay
114        do ig=1,ngrid
115          zq(ig,l,igcm_h2o_vap)=
116     &      pq(ig,l,igcm_h2o_vap)+pdq(ig,l,igcm_h2o_vap)*ptimestep
117          zq(ig,l,igcm_h2o_vap)=max(zq(ig,l,igcm_h2o_vap),1.E-30) ! FF 12/2004
118          zq0(ig,l,igcm_h2o_vap)=zq(ig,l,igcm_h2o_vap)
119          zt(ig,l)=pt(ig,l)+ pdt(ig,l)*ptimestep
120
121          zq(ig,l,igcm_h2o_ice)=
122     &      pq(ig,l,igcm_h2o_ice)+pdq(ig,l,igcm_h2o_ice)*ptimestep
123          zq(ig,l,igcm_h2o_ice)=max(zq(ig,l,igcm_h2o_ice),0.) ! FF 12/2004
124          zq0(ig,l,igcm_h2o_ice)=zq(ig,l,igcm_h2o_ice)
125        enddo
126      enddo
127
128      do l=1,nlay
129        do ig=1,ngrid
130
131c         Typical dust radius profile:
132          rdusttyp(ig,l)= max(.8e-6*exp(-pzlay(ig,l)/18000.),1.e-9)
133
134c         Typical CCN profile:
135c         Corrected equation, following Montmessin et al. 2004
136c           (N0=2e6 m-3 has been converted into N0=1.3e8 kg-1, otherwise
137c            the equation for rice is not homogeneous...)
138          ccntyp(ig,l)=
139     &       1.3e+8*max(tau(ig,1),0.001)/0.1*exp(-pzlay(ig,l)/10000.)
140c         The previously used profile was not correct:
141c         ccntyp(ig,l)=( epaisseur(ig,l)/masse(ig,l) ) *
142c    &       2.e+6/0.1*max(tau(ig,1),0.001)*exp(-pzlay(ig,l)/10000.)
143
144c         Reduce number of nuclei
145!         TEMPORAIRE : decrease the number of CCNs FF 04/200
146!         reduction facteur 3
147!         ccntyp(ig,l) = ccntyp(ig,l) / 27.
148!         reduction facteur 2
149!         ccntyp(ig,l) = ccntyp(ig,l) / 8.
150c -----------------------------------------------------------------
151          ccntyp(ig,l) = ccntyp(ig,l) / ccn_factor
152
153        enddo ! of do ig=1,ngrid
154      enddo ! of dol=1,nlay
155
156      pdqscloud(1:ngrid,1:nq)=0
157      pdqcloud(1:ngrid,1:nlay,1:nq)=0
158      pdtcloud(1:ngrid,1:nlay)=0
159
160c     ----------------------------------------------
161c
162c
163c     Rapport de melange a saturation dans la couche l : -------
164c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
165
166      call watersat(ngridmx*nlayermx,zt,pplay,zqsat)
167
168c     taux de condensation (kg/kg/s-1) dans les differentes couches
169c     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
170
171      do l=1,nlay
172        do ig=1,ngrid
173
174          if (zq(ig,l,igcm_h2o_vap).ge.zqsat(ig,l))then  !  Condensation
175            dzq=zq(ig,l,igcm_h2o_vap)-zqsat(ig,l)               
176          elseif(zq(ig,l,igcm_h2o_vap).lt.zqsat(ig,l))then  ! Sublimation
177            dzq=-min(zqsat(ig,l)-zq(ig,l,igcm_h2o_vap),
178     &               zq(ig,l,igcm_h2o_ice))
179          endif
180
181c         Water Mass change
182c         ~~~~~~~~~~~~~~~~~
183          zq(ig,l,igcm_h2o_ice)=zq(ig,l,igcm_h2o_ice)+dzq
184          zq(ig,l,igcm_h2o_vap)=zq(ig,l,igcm_h2o_vap)-dzq
185         
186          Mcon_out(ig,l) = dzq
187
188c         Calcul du rayon moyen des particules de glace.
189c         Hypothese : Dans une couche, la glace presente se
190c         repartit uniformement autour du nbre de poussieres
191c         dont le rayon moyen est prescrit par rdusttyp.
192c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
193          rice(ig,l)=max( CBRT ( (zq(ig,l,igcm_h2o_ice)/rho_ice
194     &      +ccntyp(ig,l)*(4./3.)*pi*rdusttyp(ig,l)**3.)
195     &      /(ccntyp(ig,l)*4./3.*pi) ), rdusttyp(ig,l))
196c         Effective variance of the size distribution
197          nuice(ig,l)=nuice_ref
198
199c         Sedimentation radius:
200c         ~~~~~~~~~~~~~~~~~~~~
201
202          rsedcloud(ig,l)=max( rice(ig,l)*(1.+nuice_sed)**3.,
203     &                         rdusttyp(ig,l) )
204          rsedcloud(ig,l)=min(rsedcloud(ig,l),1.e-4)
205
206        enddo ! of do ig=1,ngrid
207      enddo ! of do l=1,nlay
208
209c     Tendance finale
210c     ~~~~~~~~~~~~~~~
211      do l=1, nlay
212        do ig=1,ngridmx
213          pdqcloud(ig,l,igcm_h2o_vap)=(zq(ig,l,igcm_h2o_vap)
214     &                            -zq0(ig,l,igcm_h2o_vap))/ptimestep
215          pdqcloud(ig,l,igcm_h2o_ice) =
216     &      (zq(ig,l,igcm_h2o_ice) - zq0(ig,l,igcm_h2o_ice))/ptimestep
217          lw=(2834.3-0.28*(zt(ig,l)-To)-0.004*(zt(ig,l)-To)**2)*1.e+3
218          pdtcloud(ig,l)=-pdqcloud(ig,l,igcm_h2o_vap)*lw/cpp
219        end do
220      end do
221
222c------------------------------------------------------------------
223c     TEST_JBM
224      IF (ngrid.eq.1) THEN
225         call WRITEDIAGFI(ngrid,"mcond","h2o condensed mass","kg",1,
226     &                    Mcon_out)
227         call WRITEDIAGFI(ngrid,"rdusttyp","rdusttyp","m",1,
228     &                    rdusttyp)
229         call WRITEDIAGFI(ngrid,"ccntyp","ccntyp","kg-1",1,
230     &                    ccntyp)
231      ENDIF
232c------------------------------------------------------------------
233      return
234      end
Note: See TracBrowser for help on using the repository browser.